| Copyright | (c) 2017 Joachim Breitner 2021 Andrew Lelechenko |
|---|---|
| License | MIT |
| Maintainer | andrew.lelechenko@gmail.com |
| Safe Haskell | None |
| Language | Haskell2010 |
Test.Tasty.Inspection
Contents
Description
Integrate inspection-testing into tasty test suites.
Synopsis
- inspectTest :: Obligation -> Q Exp
- inspectObligations :: [Name -> Obligation] -> Name -> Q Exp
- inspectNames :: (Name -> Obligation) -> [Name] -> Q Exp
- data Obligation
- mkObligation :: Name -> Property -> Obligation
- data Property
- = EqualTo Name Equivalence
- | NoTypes [Name]
- | NoAllocation
- | NoTypeClasses [Name]
- | NoUseOf [Name]
- | CoreOf
- (===) :: Name -> Name -> Obligation
- (==-) :: Name -> Name -> Obligation
- (==~) :: Name -> Name -> Obligation
- hasNoType :: Name -> Name -> Obligation
- hasNoTypes :: Name -> [Name] -> Obligation
- hasNoGenerics :: Name -> Obligation
- hasNoTypeClasses :: Name -> Obligation
- hasNoTypeClassesExcept :: Name -> [Name] -> Obligation
- doesNotUse :: Name -> Name -> Obligation
- doesNotUseAnyOf :: Name -> [Name] -> Obligation
- coreOf :: Name -> Obligation
Documentation
inspectTest :: Obligation -> Q Exp Source #
Create a tasty TestTree from an Obligation:
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -O -dsuppress-all -dno-suppress-type-signatures -fplugin=Test.Tasty.Inspection.Plugin #-}
import Test.Tasty
import Test.Tasty.Inspection
lhs :: (a -> b) -> Maybe a -> Bool
lhs f x = case fmap f x of
Nothing -> True
Just{} -> False
rhs :: (a -> b) -> Maybe a -> Bool
rhs _ Nothing = True
rhs _ Just{} = False
main :: IO ()
main = defaultMain $(inspectTest $ 'lhs === 'rhs)This is not the same function as inspectTest:
both return Q Exp, but this one represents TestTree
instead of Result.
If you are unhappy with an autogenerated test name,
amend it using testName:
inspectTest (obl { testName = Just "foo" })To invert an obligation apply expectFail.
inspectObligations :: [Name -> Obligation] -> Name -> Q Exp Source #
Create a tasty TestTree, which tests several Obligations
for the same Name, generating a testGroup.
inspectNames :: (Name -> Obligation) -> [Name] -> Q Exp Source #
Create a tasty TestTree, which tests an Obligation
for several Names, generating a testGroup.
Obligations
Mostly reexported from Test.Inspection.
data Obligation #
This data type describes an inspection testing obligation.
It is recommended to build it using mkObligation, for backwards
compatibility when new fields are added. You can also use the more
mnemonic convenience functions like (===) or hasNoType.
The obligation needs to be passed to inspect or inspectTest.
Instances
| Data Obligation | |
Defined in Test.Inspection Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Obligation -> c Obligation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Obligation # toConstr :: Obligation -> Constr # dataTypeOf :: Obligation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Obligation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Obligation) # gmapT :: (forall b. Data b => b -> b) -> Obligation -> Obligation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Obligation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Obligation -> r # gmapQ :: (forall d. Data d => d -> u) -> Obligation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Obligation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Obligation -> m Obligation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Obligation -> m Obligation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Obligation -> m Obligation # | |
mkObligation :: Name -> Property -> Obligation #
Creates an inspection obligation for the given function name with default values for the optional fields.
Properties of the obligation target to be checked.
Constructors
| EqualTo Name Equivalence | Are the two functions equal? More precisely: In general The |
| NoTypes [Name] | Do none of these types appear anywhere in the definition of the function (neither locally bound nor passed as arguments) |
| NoAllocation | Does this function perform no heap allocations. |
| NoTypeClasses [Name] | Does this value contain dictionaries (except of the listed classes). |
| NoUseOf [Name] | Does not contain this value (in terms or patterns) |
| CoreOf | Always satisfied, but dumps the value in non-quiet mode. |
Instances
| Data Property | |
Defined in Test.Inspection Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Property -> c Property # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Property # toConstr :: Property -> Constr # dataTypeOf :: Property -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Property) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Property) # gmapT :: (forall b. Data b => b -> b) -> Property -> Property # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Property -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Property -> r # gmapQ :: (forall d. Data d => d -> u) -> Property -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Property -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Property -> m Property # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Property -> m Property # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Property -> m Property # | |
(==-) :: Name -> Name -> Obligation infix 9 #
Declare two functions to be equal, but ignoring
type lambdas, type arguments, type casts and hpc ticks (see EqualTo).
Note that -fhpc can prevent some optimizations; build without for more reliable analysis.
(==~) :: Name -> Name -> Obligation infix 9 #
hasNoType :: Name -> Name -> Obligation #
Declare that in a function’s implementation, the given type does not occur.
More precisely: No locally bound variable (let-bound, lambda-bound or pattern-bound) has a type that contains the given type constructor.
inspect$ fusedFunction`hasNoType`''[]
hasNoTypes :: Name -> [Name] -> Obligation Source #
Declare that given types do not occur in a function’s implementation.
hasNoGenerics :: Name -> Obligation #
Declare that a function’s implementation does not contain any generic types.
This is just hasNoType applied to the usual type constructors used in
GHC.Generics.
inspect $ hasNoGenerics genericFunction
hasNoTypeClasses :: Name -> Obligation #
Declare that a function's implementation does not include dictionaries.
More precisely: No locally bound variable (let-bound, lambda-bound or pattern-bound) has a type that contains a type that mentions a type class.
inspect$hasNoTypeClassesspecializedFunction
hasNoTypeClassesExcept :: Name -> [Name] -> Obligation #
A variant of hasNoTypeClasses, which white-lists some type-classes.
inspect$ fieldLens`hasNoTypeClassesExcept`[''Functor]
doesNotUse :: Name -> Name -> Obligation #
Declare that a function's implementation does not use the given variable (either in terms or -- if it is a constructor -- in patterns).
inspect$ foo`doesNotUse`'error
doesNotUseAnyOf :: Name -> [Name] -> Obligation Source #
Declare that given entities do not occur in a function’s implementation.