envparse-0.5.0: Parse environment variables
Safe HaskellSafe-Inferred
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 #

default record :: (r ~ Rep a, Generic a, GRecord e r) => 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 #

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

Instances

Instances details
Field e Bool Source #

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

Instance details

Defined in Env.Generic

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

Expects a single-character String value.

Instance details

Defined in Env.Generic

AsUnset e => Field e String Source #

Uses the String value verbatim.

Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Double Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Float Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Natural Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Word64 Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Word32 Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Word16 Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Word8 Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Word Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Integer Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Int64 Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Int32 Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Int16 Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Int8 Source # 
Instance details

Defined in Env.Generic

(AsUnset e, AsUnread e) => Field e Int Source # 
Instance details

Defined in Env.Generic

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

Augments the underlying field parser with the help message.

Instance details

Defined in Env.Generic

Methods

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

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

Instances

Instances details
(KnownSymbol tag, Field e a) => Field e (a ? tag) Source #

Augments the underlying field parser with the help message.

Instance details

Defined in Env.Generic

Methods

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

Functor ((?) a :: Type -> Type) Source # 
Instance details

Defined in Env.Generic

Methods

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

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

Foldable ((?) a :: Type -> Type) Source # 
Instance details

Defined in Env.Generic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Traversable ((?) a :: Type -> Type) Source # 
Instance details

Defined in Env.Generic

Methods

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

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

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

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

Eq a => Eq (a ? tag) Source # 
Instance details

Defined in Env.Generic

Methods

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

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

Show a => Show (a ? tag) Source # 
Instance details

Defined in Env.Generic

Methods

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

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

showList :: [a ? tag] -> ShowS #

class Generic a #

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

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances

Instances details
Generic Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic ()

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type #

Methods

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

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

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic All

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type #

Generic SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic [a]

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a) :: Type -> Type #

Methods

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

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

Generic (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a) :: Type -> Type #

Methods

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

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

Generic (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m) :: Type -> Type #

Generic (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Option a) :: Type -> Type #

Methods

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

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

Generic (ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

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

Methods

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

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

Generic (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: Type -> Type #

Methods

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

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

Generic (First a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

Associated Types

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

Methods

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

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

Generic (Last a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

Associated Types

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

Methods

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

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

Generic (Dual a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Endo a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Down a)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type #

Methods

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

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

Generic (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

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

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

Generic (Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (U1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (a, b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b) :: Type -> Type #

Methods

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

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

Generic (WrappedMonad m a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

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

Methods

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

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

Generic (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

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

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

Generic (Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (a, b, c)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (WrappedArrow a b c)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Associated Types

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

Methods

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

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

Generic (Kleisli m a b)

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

Associated Types

type Rep (Kleisli m a b) :: Type -> Type #

Methods

from :: Kleisli m a b -> Rep (Kleisli m a b) x #

to :: Rep (Kleisli m a b) x -> Kleisli m a b #

Generic (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: Type -> Type #

Methods

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

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

Generic (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type #

Methods

from :: Ap f a -> Rep (Ap f a) x #

to :: Rep (Ap f a) x -> Ap f a #

Generic (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: Type -> Type #

Methods

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

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

Generic (K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

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)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (a, b, c, d)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

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 ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

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)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

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)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

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