b9-0.5.68.2: A tool and library for building virtual machine images.

Safe HaskellNone
LanguageHaskell2010

B9.Environment

Description

An Environment contains textual key value pairs, relavant for string template substitution.

The variables are passed to the B9 build either via command line, OS environment variables or configuration file.

Since: 0.5.62

Synopsis

Documentation

data Environment Source #

A map of textual keys to textual values.

Since: 0.5.62

Instances
Eq Environment Source # 
Instance details

Defined in B9.Environment

Data Environment Source # 
Instance details

Defined in B9.Environment

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Environment -> c Environment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Environment #

toConstr :: Environment -> Constr #

dataTypeOf :: Environment -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Environment) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Environment) #

gmapT :: (forall b. Data b => b -> b) -> Environment -> Environment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Environment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Environment -> r #

gmapQ :: (forall d. Data d => d -> u) -> Environment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Environment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Environment -> m Environment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Environment -> m Environment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Environment -> m Environment #

Show Environment Source # 
Instance details

Defined in B9.Environment

Generic Environment Source # 
Instance details

Defined in B9.Environment

Associated Types

type Rep Environment :: Type -> Type #

Semigroup Environment Source # 
Instance details

Defined in B9.Environment

Monoid Environment Source # 
Instance details

Defined in B9.Environment

NFData Environment Source # 
Instance details

Defined in B9.Environment

Methods

rnf :: Environment -> () #

type Rep Environment Source # 
Instance details

Defined in B9.Environment

type Rep Environment = D1 (MetaData "Environment" "B9.Environment" "b9-0.5.68.2-H3TJySYVfAUHKSkQXiebpT" False) (C1 (MetaCons "MkEnvironment" PrefixI True) (S1 (MetaSel (Just "nextPosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "fromEnvironment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text Text))))

fromStringPairs :: [(String, String)] -> Environment Source #

Create an Environment from a list of pairs (Strings). Duplicated entries are ignored.

Since: 0.5.62

addBinding :: Member ExcB9 e => (Text, Text) -> Environment -> Eff e Environment Source #

Insert a key value binding to the Environment.

Throw DuplicateKey if the key already exists, but the value is not equal to the given value.

Since: 0.5.67

addStringBinding :: Member ExcB9 e => (String, String) -> Environment -> Eff e Environment Source #

Insert Strings into the Environment, see addBinding.

Since: 0.5.62

addLocalStringBinding :: (Member EnvironmentReader e, Member ExcB9 e) => (String, String) -> Eff e a -> Eff e a Source #

Insert a value into an Environment like addStringBinding, but add it to the environment of the given effect, as in localEnvironment.

Since: 0.5.65

addPositionalArguments :: [Text] -> Environment -> Environment Source #

If environment variables arg_1 .. arg_n are bound and a list of k additional values are passed to this function, store them with keys arg_(n+1) .. arg_(n+k).

Note that the Environment contains an index of the next position.

Since: 0.5.62

addLocalPositionalArguments :: Member EnvironmentReader e => [String] -> Eff e a -> Eff e a Source #

Convenient wrapper around addPositionalArguments and localEnvironment.

Since: 0.5.65

type EnvironmentReader = Reader Environment Source #

A monad transformer providing a MonadReader instance for Environment

Since: 0.5.62

hasKey :: Member EnvironmentReader e => Text -> Eff e Bool Source #

A predicate that is satisfied when a key exists in the environment.

Since: 0.5.64

runEnvironmentReader :: Environment -> Eff (EnvironmentReader ': e) a -> Eff e a Source #

Run a ReaderT of Environment.

Since: 0.5.62

localEnvironment :: Member EnvironmentReader e => (Environment -> Environment) -> Eff e a -> Eff e a Source #

Run a computation with a modified Environment

Since: 0.5.62

lookupOrThrow :: '[ExcB9, EnvironmentReader] <:: e => Text -> Eff e Text Source #

Lookup a key for a value.

throwM a KeyNotFound Exception if no value with the given key exists in the Environment.

@Since 0.5.62

lookupEither :: Member EnvironmentReader e => Text -> Eff e (Either KeyNotFound Text) Source #

Lookup a key for a value.

Return Either Left KeyNotFound, if no value with the given key exists in the Environment, or Right the value.

@Since 0.5.62

data KeyNotFound Source #

An Exception thrown by lookupOrThrow indicating that a key does not exist.

@Since 0.5.62

data DuplicateKey Source #

An Exception thrown by addBinding indicating that a key already exists.

@Since 0.5.62