test-karya-0.0.3: Testing framework.

Safe HaskellNone
LanguageHaskell2010

EL.Test.Testing

Contents

Description

Basic testing utilities.

Synopsis

Documentation

data Config Source #

Constructors

Config 

Fields

Instances
Show Config Source # 
Instance details

Defined in EL.Test.Testing

withTestName :: Text -> IO a -> IO a Source #

Set configTestName. This is a grody hack, but I need it because GHC call stack is off by one, so you get the caller line number, but the callee's function name: https://ghc.haskell.org/trac/ghc/ticket/11686

metadata

data ModuleMeta Source #

Constructors

ModuleMeta 

Fields

  • initialize :: IO () -> IO ()

    Wrap each test with IO level setup and teardown. Sync exceptions are caught from the test function, so this should only see async exceptions.

  • tags :: [Tag]
     

data Tag Source #

Constructors

Large

Especially expensive to run.

Instances
Eq Tag Source # 
Instance details

Defined in EL.Test.Testing

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Show Tag Source # 
Instance details

Defined in EL.Test.Testing

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

assertions

checkVal :: Show a => HasCallStack => a -> (a -> Bool) -> IO Bool Source #

Check against a function. Use like:

checkVal (f x) $ \case -> ...

equal :: (HasCallStack, Show a, Eq a) => a -> a -> IO Bool Source #

equalFmt :: (HasCallStack, Eq a, Show a) => (a -> Text) -> a -> a -> IO Bool Source #

rightEqual :: (HasCallStack, Show err, Show a, Eq a) => Either err a -> a -> IO Bool Source #

notEqual :: (HasCallStack, Show a, Eq a) => a -> a -> IO Bool Source #

equalf :: (HasCallStack, Show a, ApproxEq a) => Double -> a -> a -> IO Bool Source #

stringsLike :: forall txt. (HasCallStack, TextLike txt) => [txt] -> [Pattern] -> IO Bool Source #

Strings in the first list match patterns in the second list, using patternMatches.

leftLike :: (HasCallStack, Show a, TextLike txt) => Either txt a -> Pattern -> IO Bool Source #

It's common for Left to be an error msg, or be something that can be converted to one.

match :: (HasCallStack, TextLike txt) => txt -> Pattern -> IO Bool Source #

type Pattern = Text Source #

Pattern as matched by patternMatches.

exception assertions

throws :: (HasCallStack, Show a) => a -> Pattern -> IO Bool Source #

The given pure value should throw an exception that matches the predicate.

io assertions

ioEqual :: (HasCallStack, Eq a, Show a) => IO a -> a -> IO Bool Source #

low level

success :: HasCallStack => Text -> IO Bool Source #

Print a msg with a special tag indicating a passing test.

failure :: HasCallStack => Text -> IO Bool Source #

Print a msg with a special tag indicating a failing test.

extracting

QuickCheck

quickcheck :: (HasCallStack, Testable prop) => prop -> IO Bool Source #

Run a quickcheck property.

qcEqual :: (Show a, Eq a) => a -> a -> Property Source #

equal for quickcheck.

pretty printing

pprint :: Show a => a -> IO () Source #

filesystem

uniqueTmpDir :: String -> IO FilePath Source #

Get a tmp dir, which will be unique for each test run.

inTmpDir :: String -> IO a -> IO a Source #

Run the computation with cwd in a new tmp dir.

tmpBaseDir :: FilePath Source #

All tmp files used by tests should go in this directory.

TODO instead of being hardcoded this should be configured per-project.

util

force :: NFData a => a -> IO () Source #