| Maintainer | Toshio Ito <debug.ito@gmail.com> |
|---|---|
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Test.Hspec.NeedEnv
Description
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 = undefinedThis 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.
Basics
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 # | |
| Enum EnvMode Source # | |
| Show EnvMode Source # | |
| Eq EnvMode Source # | |
| Ord EnvMode 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.
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.