richenv-0.1.0.1: Rich environment variable setup for Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

RichEnv

Description

This module provides functions to set environment variables or retrieve an environment variable list according to a RichEnv object input, which defines:

  • A list of environment variables to be set with their values.
  • Mapping the name from one existing environment variable name to another (If there's an environment variable FOO=bar, a mapping ("SOME", "FOO") will generate an environment variable definition SOME with the contents of the variable FOO).
  • Mapping the prefixes of existing environment variables to a new prefix (If there's an environment variable FOO_VAR=bar, a prefix mapping ("SOME", ["FOO"]) will generate an environment variable definition SOME_VAR with the contents of the variable FOO_VAR).
Synopsis

Types

data RichEnv Source #

Type that represents a set of rules that generate environment variables. A value of this type can be retrieved from a configuration file (e.g. YAML) due to its FromJSON instance, or persisted into one with ToJSON.

Constructors

RichEnv 

Fields

  • values :: Values

    A list of environment variables to be set with their values.

  • mappings :: Mappings

    Mappings from one existing environment variable name to another.

  • prefixes :: Prefixes

    Mappings from different prefixes of existing environment variables to new prefixes.

Instances

Instances details
Monoid RichEnv Source # 
Instance details

Defined in RichEnv.Types

Semigroup RichEnv Source # 
Instance details

Defined in RichEnv.Types

Generic RichEnv Source # 
Instance details

Defined in RichEnv.Types

Associated Types

type Rep RichEnv :: Type -> Type #

Methods

from :: RichEnv -> Rep RichEnv x #

to :: Rep RichEnv x -> RichEnv #

Show RichEnv Source # 
Instance details

Defined in RichEnv.Types

Eq RichEnv Source # 
Instance details

Defined in RichEnv.Types

Methods

(==) :: RichEnv -> RichEnv -> Bool #

(/=) :: RichEnv -> RichEnv -> Bool #

FromJSON RichEnv Source # 
Instance details

Defined in RichEnv.Types

ToJSON RichEnv Source # 
Instance details

Defined in RichEnv.Types

type Rep RichEnv Source # 
Instance details

Defined in RichEnv.Types

type Rep RichEnv = D1 ('MetaData "RichEnv" "RichEnv.Types" "richenv-0.1.0.1-inplace" 'False) (C1 ('MetaCons "RichEnv" 'PrefixI 'True) (S1 ('MetaSel ('Just "values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Values) :*: (S1 ('MetaSel ('Just "mappings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mappings) :*: S1 ('MetaSel ('Just "prefixes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Prefixes))))

type Environment = [(Text, Text)] Source #

A list of key-value pairs representing environment variables.

Environment transformations

toEnvList :: RichEnv -> Environment -> Environment Source #

Get a key-value list of environment variables processing the passed environment with the RichEnv input.

toEnvList re env = valuesToEnvList (toEnvValues re env)

toEnvMap :: RichEnv -> Environment -> HashMap Text Text Source #

Get a hashmap of environment variables processing the passed environment with the RichEnv input. The idea is that the output could be passed to functions like Yaml's applyEnvValue.

toEnvMap re env = unValues (toEnvValues re env)

Functions using IO to get the environment from the current process

setRichEnv :: RichEnv -> Environment -> IO () Source #

Sets the environment variables available for the current process abiding to the RichEnv rules.

setRichEnvFromCurrent :: RichEnv -> IO () Source #

Sets the environment variables available for the current process by checking the current environment variables and applying the RichEnv rules.

setRichEnvFromCurrent re = getEnvironment >>= setRichEnv re . toEnvironment

toEnvListFromCurrent :: RichEnv -> IO Environment Source #

Get a key-value list of environment variables processing the current environment with the RichEnv input.

toEnvListFromCurrent re = toEnvList re . toEnvironment <$> getEnvironment

toEnvMapFromCurrent :: RichEnv -> IO (HashMap Text Text) Source #

Get a hashmap of environment variables processing the current environment with the RichEnv input. The idea is that the output could be passed to functions like Yaml's applyEnvValue.

toEnvMapFromCurrent re = toEnvMap re . toEnvironment <$> getEnvironment

clearEnvironment :: [(String, String)] -> IO () Source #

Clears all environment variables of the current process.