Copyright | (c) Joachim Breitner 2017 |
---|---|
License | MIT |
Maintainer | mail@joachim-breitner.de |
Portability | GHC specifc |
Safe Haskell | None |
Language | Haskell2010 |
This module supports the accompanying GHC plugin Test.Inspection.Plugin and adds to GHC the ability to do inspeciton testing.
- inspect :: Obligation -> Q [Dec]
- data Obligation = Obligation {}
- mkObligation :: Name -> Property -> Obligation
- data Property
- (===) :: Name -> Name -> Obligation
- (=/=) :: Name -> Name -> Obligation
- hasNoType :: Name -> Name -> Obligation
Synopsis
To use inspection testing, you need to
- enable the
TemplateHaskell
langauge extension - load the plugin using
-fplugin Test.Inspection.Plugin
- declare your proof obligations using
inspect
An example module is
{-# LANGAUGE TemplateHaskell #-} {-# OPTIONS_GHC -O -fplugin Test.Inspection.Plugin #-} module Simple where import Test.Inspection import Data.Maybe lhs, rhs :: (a -> b) -> Maybe a -> Bool lhs f x = isNothing (fmap f x) rhs f Nothing = True rhs f (Just _) = False inspect $ 'lhs === 'rhs
Registering obligations
inspect :: Obligation -> Q [Dec] Source #
As seen in the example above, the entry point to inspection testing is the
inspect
function, to which you pass an Obligation
.
Defining obligations
data Obligation Source #
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
memonic convenience functions like '(===)' or hasNoType
.
The obligation needs to be passed to inspect
.
Obligation | |
|
mkObligation :: Name -> Property -> Obligation Source #
Creates an inspection obligation for the given function name with default values for the optional fields.
Properties of the obligation target to be checked.
EqualTo Name | Are the two functions equal? More precisely: |
NoType Name | Does this type not occur anywhere in the definition of the function (neither locally bound nor passed as arguments) |
NoAllocation | Does this function perform no heap allocations. |
(===) :: Name -> Name -> Obligation infix 1 Source #
Convenience function to declare two functions to be equal