{-# LANGUAGE CPP #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Test.Hspec.Core.Spec.Monad ( -- RE-EXPORTED from Test.Hspec.Core.Spec Spec , SpecWith , SpecM (SpecM) , runSpecM , fromSpecList , runIO , mapSpecForest , mapSpecItem , mapSpecItem_ , modifyParams , modifyConfig -- END RE-EXPORTED from Test.Hspec.Core.Spec , Env(..) , withEnv ) where import Prelude () import Test.Hspec.Core.Compat import Control.Monad.IO.Class (liftIO) import Control.Monad.Trans.Reader import Control.Monad.Trans.Writer import Test.Hspec.Core.Example import Test.Hspec.Core.Tree import Test.Hspec.Core.Config.Definition (Config) -- | A `SpecWith` that can be evaluated directly by the -- `Test.Hspec.Core.Runner.hspec` function as it does not require any -- parameters. type Spec = SpecWith () -- | A @'SpecWith' a@ represents a test or group of tests that require an @a@ -- value to run. -- -- In the common case, a 'Spec' is a @'SpecWith' ()@ which requires @()@ and -- can thus be executed with `Test.Hspec.Core.Runner.hspec'. -- -- To supply an argument to `SpecWith` tests to turn them into `Spec`, use -- functions from "Test.Hspec.Core.Hooks" such as -- `Test.Hspec.Core.Hooks.around`, `Test.Hspec.Core.Hooks.before', -- `Test.Hspec.Core.Hooks.mapSubject' and similar. -- -- Values of this type are created by `Test.Hspec.Core.Spec.it`, -- `Test.Hspec.Core.Spec.describe` and similar. type SpecWith a = SpecM a () -- | -- @since 2.10.0 modifyConfig :: (Config -> Config) -> SpecWith a modifyConfig f = SpecM $ tell (Endo f, mempty) -- | A writer monad for `SpecTree` forests. -- -- This is used by `Test.Hspec.Core.Spec.describe` and is used -- to construct the forest of spec items. -- -- It allows for dynamically generated spec trees, for example, by using data -- obtained by performing IO actions with 'runIO'. #ifndef __MHS__ newtype SpecM a r = SpecM { unSpecM :: WriterT (Endo Config, [SpecTree a]) (ReaderT Env IO) r } deriving (Functor, Applicative, Monad) #else data SpecM a r = SpecM { unSpecM :: WriterT (Endo Config, [SpecTree a]) (ReaderT Env IO) r } deriving Functor instance Applicative (SpecM a) where pure x = SpecM $ pure x SpecM f <*> SpecM x = SpecM $ f <*> x instance Monad (SpecM a) where SpecM m >>= k = SpecM $ m >>= unSpecM . k #endif -- | Convert a `Spec` to a forest of `SpecTree`s. runSpecM :: SpecWith a -> IO (Endo Config, [SpecTree a]) runSpecM = flip runReaderT (Env []) . execWriterT . unSpecM -- | Create a `Spec` from a forest of `SpecTree`s. fromSpecForest :: (Endo Config, [SpecTree a]) -> SpecWith a fromSpecForest = SpecM . tell -- | Create a `Spec` from a forest of `SpecTree`s. fromSpecList :: [SpecTree a] -> SpecWith a fromSpecList = fromSpecForest . (,) mempty -- | Run an IO action while constructing the spec tree. -- -- `SpecM` is a monad to construct a spec tree, without executing any spec -- items itself. @runIO@ allows you to run IO actions during this construction phase. -- The IO action is always run when the spec tree is constructed (e.g. even -- when @--dry-run@ is specified). -- If you do not need the result of the IO action to construct the spec tree, -- `Test.Hspec.Core.Hooks.beforeAll` may be more suitable for your use case. runIO :: IO r -> SpecM a r runIO = SpecM . liftIO mapSpecForest :: ([SpecTree a] -> [SpecTree b]) -> SpecM a r -> SpecM b r mapSpecForest f (SpecM specs) = SpecM (mapWriterT (fmap (fmap (second f))) specs) -- {-# DEPRECATED mapSpecItem "Use `mapSpecItem_` instead." #-} -- | Deprecated: Use `mapSpecItem_` instead. mapSpecItem :: (ActionWith a -> ActionWith b) -> (Item a -> Item b) -> SpecWith a -> SpecWith b mapSpecItem _ = mapSpecItem_ mapSpecItem_ :: (Item a -> Item b) -> SpecWith a -> SpecWith b mapSpecItem_ = mapSpecForest . bimapForest id -- | Modifies the `Params` on the spec items to be generated by `SpecWith`. modifyParams :: (Params -> Params) -> SpecWith a -> SpecWith a modifyParams f = mapSpecItem_ $ \item -> item {itemExample = \p -> (itemExample item) (f p)} newtype Env = Env { -- | The path of _parent_ `Hspec.Core.Spec.describe` labels from innermost to -- outermost. envSpecDescriptionPath :: [String] } -- | Applies a function to modify the `Env` of items being written by a child -- spec writer. -- -- This is used to implement `Hspec.Core.Spec.describe`. withEnv :: (Env -> Env) -> SpecM a r -> SpecM a r withEnv f = SpecM . WriterT . local f . runWriterT . unSpecM