| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
System.Environment.Guard
Description
Functions for conditionally running IO actions based on an environment
variable.
Since: 0.1
Synopsis
- data ExpectEnv
- withGuard :: String -> ExpectEnv -> IO a -> IO (Maybe a)
- withGuard_ :: String -> ExpectEnv -> IO a -> IO ()
- guardOrElse :: String -> ExpectEnv -> IO a -> IO e -> IO (Either e a)
- guardOrElse' :: String -> ExpectEnv -> IO a -> IO a -> IO a
- guardSet :: String -> IO a -> IO (Maybe a)
- guardSet_ :: String -> IO a -> IO ()
- guardExpected :: String -> String -> IO a -> IO (Maybe a)
- guardExpected_ :: String -> String -> IO a -> IO ()
- guardPredicate :: String -> (String -> Bool) -> IO a -> IO (Maybe a)
- guardPredicate_ :: String -> (String -> Bool) -> IO a -> IO ()
High level combinators
The expectation for an environment variable lookup.
Since: 0.1.1
Constructors
| ExpectEnvSet | Expect that the environment variable is set (i.e. contents can be anything). Since: 0.1.1 |
| ExpectEnvEquals String | Expect that the environment variable is set and the contents equals the string. This is case-insensitive. Since: 0.1.1 |
| ExpectEnvPredicate (String -> Bool) | Expect that the environment variable is set and its contents satisfies the predicate. Since: 0.1.1 |
withGuard :: String -> ExpectEnv -> IO a -> IO (Maybe a) Source #
Guards an action behind an environment variable according to the given expectation.
Examples
>>>setEnv "FOO" "bar">>>withGuard "FOO" (ExpectEnvEquals "baz") (putStrLn "succeeded")Nothing
>>>withGuard "FOO" ExpectEnvSet (putStrLn "succeeded")succeeded Just ()
Since: 0.1.1
withGuard_ :: String -> ExpectEnv -> IO a -> IO () Source #
Variant of withGuard that ignores the return value.
Since: 0.1.1
Arguments
| :: String | The environment variable. |
| -> ExpectEnv | The expectation. |
| -> IO a | The action to run if the expectation succeeds. |
| -> IO e | The action to run if the expectation fails. |
| -> IO (Either e a) | The result. |
guardOrElse var expect io1 io2 is equivalent to
withGuard var expect io1 except that it runs io2 if io1 is not run.
Examples
>>>setEnv "FOO" "bar">>>guardOrElse "FOO" ExpectEnvSet (pure True) (pure "not found")Right True
>>>guardOrElse "BAR" ExpectEnvSet (pure True) (pure "not found")Left "not found"
Since: 0.1.1
Arguments
| :: String | The environment variable. |
| -> ExpectEnv | The expectation. |
| -> IO a | The action to run if the expectation succeeds. |
| -> IO a | The action to run if the expectation fails. |
| -> IO a | The result. |
guardOrElse specialized to the same type so that we always return an
a. This can also be used to ignore the return value i.e.
guardOrElse' var expect (void io1) io2
Examples
>>>setEnv "FOO" "bar">>>guardOrElse' "FOO" ExpectEnvSet (pure True) (pure False)True
>>>guardOrElse' "BAR" ExpectEnvSet (pure True) (pure False)False
>>>guardOrElse' "BAR" ExpectEnvSet (void $ pure True) (putStrLn "not found")not found
Since: 0.1.1
Low level functions
Checking environment variable is set
guardSet :: String -> IO a -> IO (Maybe a) Source #
runs guardSet var ioio iff
- The environment variable
varis set.
guardSetvar ===guardPredicatevar (constTrue)
Examples
>>>guardSet "NOT_SET" (putStrLn "ran io" $> True)Nothing
>>>setEnv "SET" "foo">>>guardSet "SET" (putStrLn "ran io" $> True)ran io Just True
Since: 0.1
guardSet_ :: String -> IO a -> IO () Source #
Variant of guardSet that ignores the return value.
Since: 0.1
Checking environment variable match
guardExpected :: String -> String -> IO a -> IO (Maybe a) Source #
runs guardExpected var expected ioio iff
- The environment variable
varis set. var's value equalsexpected. This is case-insensitive.
guardExpectedvar expected ===guardPredicatevar (\a b ->fmaptoLowera ==fmaptoLowerb)
Examples
>>>guardExpected "NOT_SET" "val" (putStrLn "ran io" $> True)Nothing
>>>setEnv "WRONG_VAL" "good_val">>>guardExpected "WRONG_VAL" "bad_val" (putStrLn "ran io" $> True)Nothing
>>>setEnv "WILL_RUN" "val">>>guardExpected "WILL_RUN" "VAL" (putStrLn "ran io" $> True)ran io Just True
Since: 0.1
guardExpected_ :: String -> String -> IO a -> IO () Source #
Variant of guardExpected_ that ignores the return value.
Since: 0.1
Checking environment variable predicate
guardPredicate :: String -> (String -> Bool) -> IO a -> IO (Maybe a) Source #
This is the most general way to check an environment variable.
runs guardPredicate var p ioio iff
- The environment variable
varis set. var's value satisfies predicatep.
Examples
>>>guardPredicate "NOT_SET" (const True) (putStrLn "ran io" $> True)Nothing
>>>setEnv "CASE_WRONG" "VAL">>>guardPredicate "CASE_WRONG" (== "val") (putStrLn "ran io" $> True)Nothing
>>>setEnv "WILL_RUN" "VAL">>>guardPredicate "WILL_RUN" (== "VAL") (putStrLn "ran io" $> True)ran io Just True
Since: 0.1
guardPredicate_ :: String -> (String -> Bool) -> IO a -> IO () Source #
Variant of guardPredicate that ignores the return value.
Since: 0.1