envy-1.3.0.0: An environmentally friendly way to deal with environment variables

Copyright(c) David Johnson 2015
Maintainerdjohnson.m@ngmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

System.Envy

Contents

Description

{-# LANGUAGE DeriveGeneric #-}

module Main ( main ) where

import System.Envy
import GHC.Generics

data PGConfig = PGConfig {
  pgHost :: String -- "PG_HOST"
, pgPort :: Int    -- "PG_PORT"
} deriving (Generic, Show)

-- Default instance used if environment variable doesn't exist
instance DefConfig PGConfig where
  defConfig = PGConfig "localhost" 5432

instance FromEnv PGConfig
-- Generically produces the following body (no implementation needed if using Generics):
-- fromEnv = PGConfig <$> envMaybe "PG_HOST" .!= "localhost"
--                    <*> envMaybe "PG_PORT" .!= 5432

main :: IO ()
main =
  print =<< do decodeEnv :: IO (Either String PGConfig)
 -- PGConfig { pgHost = "custom-pg-url", pgPort = 5432 }

Synopsis

Classes

class FromEnv a where Source #

FromEnv Typeclass w/ Generic default implementation

Methods

fromEnv :: Parser a Source #

fromEnv :: (DefConfig a, Generic a, GFromEnv (Rep a)) => Parser a Source #

class ToEnv a where Source #

Type class for objects which can be converted to a set of environment variable settings.

Minimal complete definition

toEnv

Methods

toEnv :: a -> EnvList a Source #

Convert an object into a list of environment variable settings.

class Typeable a => Var a where Source #

Class for converting to / from an environment variable

Minimal complete definition

toVar, fromVar

Methods

toVar :: a -> String Source #

Convert a value into an environment variable.

fromVar :: String -> Maybe a Source #

Parse an environment variable.

Instances

Var Bool Source # 
Var Double Source # 
Var Int Source # 
Var Int8 Source # 
Var Int16 Source # 
Var Int32 Source # 
Var Int64 Source # 
Var Integer Source # 
Var Word8 Source # 
Var Word16 Source # 
Var Word32 Source # 
Var Word64 Source # 
Var String Source # 
Var ByteString Source # 
Var ByteString Source # 
Var Text Source # 
Var Text Source # 
Var UTCTime Source # 
Var Day Source # 

data EnvList a Source #

List of environment variables. Captures a "phantom type" which allows the type checker to detect the proper implementation of toEnv to use.

Instances

Show (EnvList a) Source # 

Methods

showsPrec :: Int -> EnvList a -> ShowS #

show :: EnvList a -> String #

showList :: [EnvList a] -> ShowS #

Functions

decodeEnv :: FromEnv a => IO (Either String a) Source #

Environment retrieval with failure info

decode :: FromEnv a => IO (Maybe a) Source #

Environment retrieval (with no failure info)

showEnv :: IO () Source #

Display all environment variables, for convenience

setEnvironment :: EnvList a -> IO (Either String ()) Source #

Set environment via a ToEnv constrained type

setEnvironment' :: ToEnv a => a -> IO (Either String ()) Source #

Set environment directly using a value of class ToEnv

unsetEnvironment :: EnvList a -> IO (Either String ()) Source #

Unset Environment from a ToEnv constrained type

unsetEnvironment' :: ToEnv a => a -> IO (Either String ()) Source #

Unset Environment using a value of class ToEnv

makeEnv :: [EnvVar] -> EnvList a Source #

Smart constructor, environment creation helper.

env Source #

Arguments

:: Var a 
=> String

Key to look up.

-> Parser a

Return a value of this type or throw an error.

Environment variable getter. Fails if the variable is not set or fails to parse.

envMaybe Source #

Arguments

:: Var a 
=> String

Key to look up.

-> Parser (Maybe a)

Return Nothing if variable isn't set.

Environment variable getter returning Maybe

(.=) Source #

Arguments

:: Var a 
=> String

The variable name to set.

-> a

Object to set in the environment.

-> EnvVar

Mapping of Variable to Value.

Infix environment variable setter Smart constructor for producing types of EnvVar

(.!=) Source #

Arguments

:: Parser (Maybe a)

Parser that might fail.

-> a

Value to return if the parser fails.

-> Parser a

Parser that returns the default on failure.

For use with envMaybe for providing default arguments.

Generics

class DefConfig a where Source #

Type class for objects which have a default configuration.

Minimal complete definition

defConfig

Methods

defConfig :: a Source #

data Option Source #

For customizing environment variable generation

Constructors

Option 

Fields

Instances

runEnv :: Parser a -> IO (Either String a) Source #

For use with Generics, no FromEnv typeclass necessary

getPgConfig :: IO (Either String ConnectInfo)
getPgConfig = runEnv $ gFromEnvCustom defOption

gFromEnvCustom :: forall a. (DefConfig a, Generic a, GFromEnv (Rep a)) => Option -> Parser a Source #

Meant for specifying a custom Option for environment retrieval

instance FromEnv PGConfig where
  fromEnv = gFromEnvCustom Option { dropPrefixCount = 8, customPrefix = "PG" }