envy: An environmentally friendly way to deal with environment variables

[ bsd3, library, system ] [ Propose Tags ]
This version is deprecated.

For package use information see the README.md


[Skip to Readme]

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.0.1, 0.2.0.0, 0.3.0.0, 0.3.0.1, 0.3.0.2, 0.3.1.2, 1.0.0.0, 1.1.0.0, 1.2.0.0, 1.2.0.1, 1.3.0.0, 1.3.0.1, 1.3.0.2, 1.5.0.0, 1.5.1.0, 2.0.0.0, 2.1.0.0, 2.1.1.0, 2.1.2.0, 2.1.3.0 (info)
Dependencies base (>=4.7 && <5), bytestring (>=0.10 && <0.11), containers (>=0.5 && <0.6), mtl (>=2.2 && <2.3), text (>=1.2 && <1.3), time (>=1.5 && <1.6), transformers (>=0.4 && <0.5) [details]
License BSD-3-Clause
Copyright David Johnson (c) 2015
Author David Johnson, Tim Adams
Maintainer djohnson.m@gmail.com
Category System
Source repo head: git clone https://github.com/dmjio/envy
Uploaded by DavidJohnson at 2015-11-10T17:00:28Z
Distributions LTSHaskell:2.1.2.0, NixOS:2.1.2.0
Reverse Dependencies 11 direct, 24 indirect [details]
Downloads 14774 total (97 in the last 30 days)
Rating 2.25 (votes: 4) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2015-11-12 [all 1 reports]

Readme for envy-0.3.1.2

[back to package description]

envy

Hackage Hackage Dependencies Haskell Programming Language BSD3 License Build Status

Let's face it, dealing with environment variables in Haskell isn't that satisfying.

import System.Environment
import Data.Text (pack)
import Text.Read (readMaybe)

data PGConfig = PGConfig {
  pgPort :: Int
  pgURL  :: Text
} deriving (Show, Eq)

getPGPort :: IO PGConfig
getPGPort = do
  portResult <- lookupEnv "PG_PORT"
  urlResult  <- lookupEnv "PG_URL"
  case (portResult, urlResult) of
    (Just port, Just url) ->
      case readMaybe port :: Maybe Int of
        Nothing -> error "PG_PORT isn't a number"
        Just portNum -> return $ PGConfig portNum (pack url)
    (Nothing, _) -> error "Couldn't find PG_PORT"    
    (_, Nothing) -> error "Couldn't find PG_URL"    
    -- Pretty gross right...

Another attempt to remedy the lookup madness is with a MaybeT IO a. See below.

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Control.Applicative
import Control.Monad.Trans.Maybe
import Control.Monad.IO.Class
import System.Environment

newtype Env a = Env { unEnv :: MaybeT IO a }
    deriving (Functor, Applicative, Monad, MonadIO, Alternative, MonadPlus)

getEnv :: Env a -> IO (Maybe a)
getEnv env = runMaybeT (unEnv env)

env :: String -> Env a
env key = Env (MaybeT (lookupEnv key))

connectInfo :: Env ConnectInfo
connectInfo = ConnectInfo
   <$> env "PG_HOST"
   <*> env "PG_PORT"
   <*> env "PG_USER"
   <*> env "PG_PASS"
   <*> env "PG_DB"

This abstraction falls short in two areas:

  • Lookups don't return any information when a variable doesn't exist (just a Nothing)
  • Lookups don't attempt to parse the returned type into something meaningful (everything is returned as a String)

What if we could apply aeson's FromJSON / ToJSON pattern to give us variable lookups that provide both key-lookup and parse failure information? Armed with the GeneralizedNewTypeDeriving extension we can derive instances of Var that will parse to and from an environment. The Var typeclass is simply:

class Var a where
  toVar   :: a -> String
  fromVar :: String -> Maybe a

With instances for most primitive types supported (Word8 - Word64, Int, Integer, String, Text, etc.) the Var class is easily deriveable. The FromEnv typeclass provides a parser type that is an instance of MonadError String and MonadIO. This allows for connection pool initialization inside of our environment parser and custom error handling. The ToEnv class allows us to create an environment configuration given any a. See below for an example.

{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE DeriveDataTypeable         #-}
------------------------------------------------------------------------------
module Main ( main ) where
------------------------------------------------------------------------------
import           Control.Applicative
import           Control.Exception
import           Control.Monad
import           Data.Either
import           Data.Word
import           System.Environment
import           System.Envy
------------------------------------------------------------------------------
data ConnectInfo = ConnectInfo {
      pgHost :: String
    , pgPort :: Word16
    , pgUser :: String
    , pgPass :: String
    , pgDB   :: String
  } deriving (Show)

------------------------------------------------------------------------------
-- | Posgtres config
data PGConfig = PGConfig {
    pgConnectInfo :: ConnectInfo -- ^ Connnection Info
  } deriving Show

------------------------------------------------------------------------------
-- | FromEnv instances support popular aeson combinators *and* IO
-- for dealing with connection pools. `env` is equivalent to (.:) in `aeson`
-- and `envMaybe` is equivalent to (.:?), except here the lookups are impure.
instance FromEnv PGConfig where
  fromEnv = PGConfig <$> (ConnectInfo <$> envMaybe "PG_HOST" .!= "localhost"
                                      <*> env "PG_PORT"
                                      <*> env "PG_USER" 
                                      <*> env "PG_PASS" 
                                      <*> env "PG_DB")

------------------------------------------------------------------------------
-- | To Environment Instances
-- (.=) is a smart constructor for producing types of `EnvVar` (which ensures
-- that Strings are set properly in an environment so they can be parsed properly
instance ToEnv PGConfig where
  toEnv PGConfig {..} = makeEnv 
       [ "PG_HOST" .= pgHost
       , "PG_PORT" .= pgPort
       , "PG_USER" .= pgUser
       , "PG_PASS" .= pgPass
       , "PG_DB"   .= pgDB  
       ]

------------------------------------------------------------------------------
-- | Example
main :: IO ()
main = do
   setEnvironment (toEnv :: EnvList PGConfig)
   print =<< do decodeEnv :: IO (Either String PGConfig)
   -- unsetEnvironment (toEnv :: EnvList PGConfig)  -- remove when done

Note: As of base 4.7 setEnv and getEnv throw an IOException if a = is present in an environment. envy catches these synchronous exceptions and delivers them purely to the end user.