{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Test.Hspec.Core.Spec.Monad (
Spec
, SpecWith
, SpecM (..)
, runSpecM
, fromSpecList
, runIO
, mapSpecItem
, mapSpecItem_
, modifyParams
) where
import Prelude ()
import Test.Hspec.Core.Compat
import Control.Arrow
import Control.Monad.Trans.Writer
import Control.Monad.IO.Class (liftIO)
import Test.Hspec.Core.Example
import Test.Hspec.Core.Tree
type Spec = SpecWith ()
type SpecWith a = SpecM a ()
newtype SpecM a r = SpecM (WriterT [SpecTree a] IO r)
deriving (Functor, Applicative, Monad)
runSpecM :: SpecWith a -> IO [SpecTree a]
runSpecM (SpecM specs) = execWriterT specs
fromSpecList :: [SpecTree a] -> SpecWith a
fromSpecList = SpecM . tell
runIO :: IO r -> SpecM a r
runIO = SpecM . liftIO
mapSpecTree :: (SpecTree a -> SpecTree b) -> SpecM a r -> SpecM b r
mapSpecTree f (SpecM specs) = SpecM (mapWriterT (fmap (second (map f))) specs)
mapSpecItem :: (ActionWith a -> ActionWith b) -> (Item a -> Item b) -> SpecWith a -> SpecWith b
mapSpecItem g f = mapSpecTree (bimapTree g f)
mapSpecItem_ :: (Item a -> Item a) -> SpecWith a -> SpecWith a
mapSpecItem_ = mapSpecItem id
modifyParams :: (Params -> Params) -> SpecWith a -> SpecWith a
modifyParams f = mapSpecItem_ $ \item -> item {itemExample = \p -> (itemExample item) (f p)}