Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Golden = Golden (IO (Maybe a)) (IO a) (a -> a -> IO GDiff) (a -> IO GShow) (Maybe (a -> IO ()))
- newtype AcceptTests = AcceptTests Bool
- readFileMaybe :: FilePath -> IO (Maybe ByteString)
- data GDiff
- data GShow = ShowText Text
- type GoldenResult = GoldenResult' IO
- type GoldenResultI = GoldenResult' Identity
- data GoldenResult' (m :: Type -> Type)
- = GREqual
- | GRDifferent a a GDiff (Maybe (a -> IO ()))
- | GRNoGolden (m a) (a -> IO GShow) (Maybe (a -> IO ()))
- runGolden :: Golden -> IO (Result, GoldenResult)
- forceGoldenResult :: GoldenResult -> IO GoldenResultI
- ifM :: Monad m => m Bool -> m a -> m a -> m a
- ifNotM :: Monad m => m Bool -> m a -> m a -> m a
- and2M :: Monad m => m Bool -> m Bool -> m Bool
- andM :: Monad m => [m Bool] -> m Bool
- or2M :: Monad m => m Bool -> m Bool -> m Bool
- orM :: Monad m => [m Bool] -> m Bool
Documentation
See goldenTest1
for explanation of the fields.
Instances
IsTest Golden Source # | |
Defined in Test.Tasty.Silver.Internal |
newtype AcceptTests Source #
This option, when set to True
, specifies that we should run in the
«accept tests» mode.
Instances
Eq AcceptTests Source # | |
Defined in Test.Tasty.Silver.Internal (==) :: AcceptTests -> AcceptTests -> Bool # (/=) :: AcceptTests -> AcceptTests -> Bool # | |
Ord AcceptTests Source # | |
Defined in Test.Tasty.Silver.Internal compare :: AcceptTests -> AcceptTests -> Ordering # (<) :: AcceptTests -> AcceptTests -> Bool # (<=) :: AcceptTests -> AcceptTests -> Bool # (>) :: AcceptTests -> AcceptTests -> Bool # (>=) :: AcceptTests -> AcceptTests -> Bool # max :: AcceptTests -> AcceptTests -> AcceptTests # min :: AcceptTests -> AcceptTests -> AcceptTests # | |
IsOption AcceptTests Source # | |
Defined in Test.Tasty.Silver.Internal parseValue :: String -> Maybe AcceptTests optionName :: Tagged AcceptTests String optionHelp :: Tagged AcceptTests String showDefaultValue :: AcceptTests -> Maybe String optionCLParser :: Parser AcceptTests |
readFileMaybe :: FilePath -> IO (Maybe ByteString) Source #
Read the file if it exists, else return Nothing
.
Useful for reading golden files.
The comparison/diff result.
type GoldenResult = GoldenResult' IO Source #
type GoldenResultI = GoldenResult' Identity Source #
data GoldenResult' (m :: Type -> Type) Source #
GREqual | |
GRDifferent a a GDiff (Maybe (a -> IO ())) | |
GRNoGolden (m a) (a -> IO GShow) (Maybe (a -> IO ())) |
Instances
Show (GoldenResult' m) Source # | |
Defined in Test.Tasty.Silver.Internal showsPrec :: Int -> GoldenResult' m -> ShowS # show :: GoldenResult' m -> String # showList :: [GoldenResult' m] -> ShowS # |