Safe Haskell | None |
---|---|
Language | GHC2021 |
Skeletest.Internal.Spec
Synopsis
- type Spec = Spec' ()
- data SpecTree
- = SpecGroup {
- groupLabel :: Text
- groupTrees :: [SpecTree]
- | SpecTest {
- testName :: Text
- testMarkers :: [SomeMarker]
- testAction :: IO TestResult
- = SpecGroup {
- runSpecs :: Hooks -> SpecRegistry -> IO Bool
- type SpecRegistry = [SpecInfo]
- data SpecInfo = SpecInfo {}
- pruneSpec :: SpecRegistry -> SpecRegistry
- applyTestSelections :: TestTargets -> SpecRegistry -> SpecRegistry
- describe :: String -> Spec -> Spec
- class MonadIO m => Testable (m :: Type -> Type) where
- runTestable :: m () -> IO TestResult
- test :: Testable m => String -> m () -> Spec
- it :: String -> IO () -> Spec
- prop :: String -> Property -> Spec
- xfail :: String -> Spec -> Spec
- skip :: String -> Spec -> Spec
- markManual :: Spec -> Spec
- class (Show a, Typeable a) => IsMarker a where
- getMarkerName :: a -> String
- withMarkers :: [String] -> Spec -> Spec
- withMarker :: IsMarker a => a -> Spec -> Spec
Spec interface
Constructors
SpecGroup | |
Fields
| |
SpecTest | |
Fields
|
runSpecs :: Hooks -> SpecRegistry -> IO Bool Source #
Run the given Specs and return whether all of the tests passed.
Entrypoint
type SpecRegistry = [SpecInfo] Source #
pruneSpec :: SpecRegistry -> SpecRegistry Source #
Defining a Spec
class MonadIO m => Testable (m :: Type -> Type) where Source #
Minimal complete definition
Methods
runTestable :: m () -> IO TestResult Source #
Instances
Testable IO Source # | |
Defined in Skeletest.Assertions Methods runTestable :: IO () -> IO TestResult Source # context :: String -> IO a -> IO a Source # throwFailure :: AssertionFail -> IO a Source # | |
Testable PropertyM Source # | |
Defined in Skeletest.Prop.Internal Methods runTestable :: PropertyM () -> IO TestResult Source # context :: String -> PropertyM a -> PropertyM a Source # throwFailure :: AssertionFail -> PropertyM a Source # |
it :: String -> IO () -> Spec Source #
Define an IO-based test.
Should typically be written to be read as full sentences in traditional BDD style: https://en.wikipedia.org/wiki/Behavior-driven_development.
describe "User" $ do
it "can be checked for equality" $ do
user1 shouldBe
user1
prop :: String -> Property -> Spec Source #
Define a property test.
describe "User" $ do prop "decode . encode === Just" $ do let genUser = ... (decode . encode) P.=== Just `shouldSatisfy` P.isoWith genUser
Modifiers
xfail :: String -> Spec -> Spec Source #
Mark the given spec as expected to fail. Fails tests if they unexpectedly pass.
Can be selected with the marker @xfail
skip :: String -> Spec -> Spec Source #
Skip all tests in the given spec.
Can be selected with the marker @skip
markManual :: Spec -> Spec Source #
Mark tests as tests that should only be run when explicitly specified on the command line.
Markers
class (Show a, Typeable a) => IsMarker a where Source #
Methods
getMarkerName :: a -> String Source #
The name of the marker that can be selected with @name
syntax.
Marker names must only include alphanumeric characters, hyphens, underscores, and periods.
Instances
IsMarker AnonMarker Source # | |
Defined in Skeletest.Internal.Markers Methods getMarkerName :: AnonMarker -> String Source # |
withMarkers :: [String] -> Spec -> Spec Source #
Adds the given names as plain markers to all tests in the given spec.
See getMarkerName
.