envy-1.1.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

Minimal complete definition

Nothing

Methods

fromEnv :: Parser a Source

class ToEnv a where Source

ToEnv Typeclass

Methods

toEnv :: a -> EnvList a Source

data EnvList a Source

EnvList type w/ phanton

Instances

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 :: ToEnv a => EnvList a -> IO (Either String ()) Source

Unset Environment from a ToEnv constrained type

makeEnv :: ToEnv a => [EnvVar] -> EnvList a Source

smart constructor, Environment creation helper

env :: forall a. (Typeable a, Var a) => String -> Parser a Source

Environment variable getter

envMaybe :: forall a. (Typeable a, Var a) => String -> Parser (Maybe a) Source

Environment variable getter returning Maybe

(.=) :: Var a => String -> a -> EnvVar Source

Infix environment variable setter Smart constructor for producing types of EnvVar

(.!=) :: forall a. (Typeable a, Var a) => Parser (Maybe a) -> a -> Parser a Source

For use with (.:?) for providing default arguments

Generics

class DefConfig a where Source

Default Config

Methods

defConfig :: a Source

data Option Source

For customizing environment variable generation

Constructors

Option 

Fields

dropPrefixCount :: Int

Applied first

customPrefix :: String

Converted toUpper

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" }