hspec-need-env-0.1.0.4: Read environment variables for hspec tests

MaintainerToshio Ito <debug.ito@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Test.Hspec.NeedEnv

Contents

Description

Synopsis:

module Synopsis (main,spec) where

import Control.Applicative ((<$>), (<*>))
import Test.Hspec (Spec, SpecWith, hspec, before, describe, it, shouldBe)
import Test.Hspec.NeedEnv (EnvMode(Need), needEnv, needEnvRead)

main :: IO ()
main = hspec spec

-- | Read environment variables for parameters necessary for testing.
getEnvs :: IO (String, Int)
getEnvs = (,)
          <$> needEnv mode "TEST_USER_NAME"
          <*> needEnvRead mode "TEST_SEED"
  where
    mode = Need

spec :: Spec
spec = before getEnvs $ specWithUserAndSeed
       -- ^ Use 'before' and similar functions to write 'SpecWith'
       -- that takes parameters.

-- | Test spec that depends on the environment variables.
specWithUserAndSeed :: SpecWith (String, Int)
specWithUserAndSeed = describe "funcUnderTest" $ do
  it "should do something" $ \(user_name, seed) -> do
    funcUnderTest user_name seed `shouldBe` "SOMETHING"

funcUnderTest :: String -> Int -> String
funcUnderTest = undefined

This module exports needEnv and other similar functions that read environment variables in hspec tests. They are useful to write tests that depend on some external entities, e.g. Web servers, database servers and random number generators.

Synopsis

Basics

data EnvMode Source #

How to treat missing environment variable.

Constructors

Need

If the environment variable is not set, the test fails.

Want

If the environment variable is not set, the test gets pending.

Instances
Bounded EnvMode Source # 
Instance details

Defined in Test.Hspec.NeedEnv

Enum EnvMode Source # 
Instance details

Defined in Test.Hspec.NeedEnv

Eq EnvMode Source # 
Instance details

Defined in Test.Hspec.NeedEnv

Methods

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

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

Ord EnvMode Source # 
Instance details

Defined in Test.Hspec.NeedEnv

Show EnvMode Source # 
Instance details

Defined in Test.Hspec.NeedEnv

needEnv Source #

Arguments

:: EnvMode 
-> String

name of the environment variable

-> IO String

value of the environment variable

Get value of the specified environment variable. If the environment variable is not set, it executes the action specified by the EnvMode.

needEnvParse Source #

Arguments

:: EnvMode 
-> (String -> Either String a)

the parser of the environment variable

-> String 
-> IO a 

Get environment variable by needEnv, and parse the value. If it fails to parse, the test fails.

needEnvRead :: Read a => EnvMode -> String -> IO a Source #

Parse the environment variable with Read class.

Utilities

needEnvHostPort Source #

Arguments

:: EnvMode 
-> String

prefix of environment variables

-> IO (String, Int) 

Get the pair of hostname and port number from environment variables.

It reads environment variables (prefix ++ "_HOST") and (prefix ++ "_PORT").