harg-0.4.0.0: Haskell program configuration using higher kinded data

Safe HaskellNone
LanguageHaskell2010

Options.Harg.Sources.Env

Synopsis

Documentation

data EnvSource (f :: Type -> Type) Source #

Source that enables a parser to read options from environment variables.

Constructors

EnvSource 
Instances
GetSource EnvSource f Source # 
Instance details

Defined in Options.Harg.Sources.Env

Associated Types

type SourceVal EnvSource :: Type Source #

Generic (EnvSource f) Source # 
Instance details

Defined in Options.Harg.Sources.Env

Associated Types

type Rep (EnvSource f) :: Type -> Type #

Methods

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

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

ProductB EnvSource Source # 
Instance details

Defined in Options.Harg.Sources.Env

Methods

bprod :: EnvSource f -> EnvSource g -> EnvSource (Product f g) #

buniq :: (forall (a :: k). f a) -> EnvSource f #

TraversableB EnvSource Source # 
Instance details

Defined in Options.Harg.Sources.Env

Methods

btraverse :: Applicative t => (forall (a :: k). f a -> t (g a)) -> EnvSource f -> t (EnvSource g) #

FunctorB EnvSource Source # 
Instance details

Defined in Options.Harg.Sources.Env

Methods

bmap :: (forall (a :: k). f a -> g a) -> EnvSource f -> EnvSource g #

type SourceVal EnvSource Source # 
Instance details

Defined in Options.Harg.Sources.Env

type Rep (EnvSource f) Source # 
Instance details

Defined in Options.Harg.Sources.Env

type Rep (EnvSource f) = D1 (MetaData "EnvSource" "Options.Harg.Sources.Env" "harg-0.4.0.0-inplace" False) (C1 (MetaCons "EnvSource" PrefixI False) (U1 :: Type -> Type))

newtype EnvSourceVal Source #

Value of EnvSource, which is an association list between environment variable names and values (strings).

Instances
FunctorB a => RunSource EnvSourceVal a Source # 
Instance details

Defined in Options.Harg.Sources.Env

lookupEnv :: Environment -> String -> Maybe String Source #

Try to get a value from the environment variable association list.