Safe Haskell | None |
---|---|
Language | Haskell98 |
- target :: Testable f => f -> String -> FilePath -> IO ()
- targetResult :: Testable f => f -> String -> FilePath -> IO Result
- targetWith :: Testable f => f -> String -> FilePath -> TargetOpts -> IO ()
- targetResultWith :: Testable f => f -> String -> FilePath -> TargetOpts -> IO Result
- targetTH :: Name -> Q (TExp (FilePath -> IO ()))
- targetResultTH :: Name -> Q (TExp (FilePath -> IO Result))
- targetWithTH :: Name -> Q (TExp (FilePath -> TargetOpts -> IO ()))
- targetResultWithTH :: Name -> Q (TExp (FilePath -> TargetOpts -> IO Result))
- data Result
- class (AllHave Targetable (Args f), Targetable (Res f), AllHave Show (Args f)) => Testable f
- class Targetable a where
- data TargetOpts = TargetOpts {}
- defaultOpts :: TargetOpts
- data Test = Testable t => T t
- monomorphic :: Name -> ExpQ
Documentation
:: Testable f | |
=> f | the function |
-> String | the name of the function |
-> FilePath | the path to the module that defines the function |
-> IO () |
Test whether a function inhabits its refinement type by enumerating valid inputs and calling the function.
targetWith :: Testable f => f -> String -> FilePath -> TargetOpts -> IO () Source #
Like target
, but accepts options to control the enumeration depth,
solver, and verbosity.
targetResultWith :: Testable f => f -> String -> FilePath -> TargetOpts -> IO Result Source #
Like targetWith
, but returns the Result
instead of printing to standard out.
targetWithTH :: Name -> Q (TExp (FilePath -> TargetOpts -> IO ())) Source #
targetResultWithTH :: Name -> Q (TExp (FilePath -> TargetOpts -> IO Result)) Source #
class (AllHave Targetable (Args f), Targetable (Res f), AllHave Show (Args f)) => Testable f Source #
A class of functions that Target can test. A function is Testable
iff
all of its component types are Targetable
and all of its argument types are
Show
able.
You should never have to define a new Testable
instance.
queryArgs, decodeArgs, apply, mkExprs
class Targetable a where Source #
A class of datatypes for which we can efficiently generate constrained values by querying an SMT solver.
If possible, instances should not be written by hand, but rather by using the default implementations via GHC.Generics, e.g.
import GHC.Generics import Test.Target.Targetable data Foo = ... deriving Generic instance Targetable Foo
query :: (?loc :: CallStack) => Proxy a -> Depth -> Symbol -> SpecType -> Target Symbol Source #
Construct an SMT query describing all values of the given type up to the
given Depth
.
decode :: Symbol -> SpecType -> Target a Source #
Reconstruct a Haskell value from the SMT model.
check :: a -> SpecType -> Target (Bool, Expr) Source #
Check whether a Haskell value inhabits the given type. Also returns a logical expression corresponding to the Haskell value.
Translate a Haskell value into a logical expression.
getType :: Proxy a -> Sort Source #
What is the Haskell type? (Mainly used to make the SMT queries more readable).
getType :: (Generic a, Rep a ~ D1 d f, Datatype d) => Proxy a -> Sort Source #
What is the Haskell type? (Mainly used to make the SMT queries more readable).
query :: (?loc :: CallStack) => (Generic a, GQuery (Rep a)) => Proxy a -> Int -> Symbol -> SpecType -> Target Symbol Source #
Construct an SMT query describing all values of the given type up to the
given Depth
.
toExpr :: (Generic a, GToExpr (Rep a)) => a -> Expr Source #
Translate a Haskell value into a logical expression.
decode :: (Generic a, GDecode (Rep a)) => Symbol -> SpecType -> Target a Source #
Reconstruct a Haskell value from the SMT model.
check :: (Generic a, GCheck (Rep a)) => a -> SpecType -> Target (Bool, Expr) Source #
Check whether a Haskell value inhabits the given type. Also returns a logical expression corresponding to the Haskell value.
Targetable Bool Source # | |
Targetable Char Source # | |
Targetable Int Source # | |
Targetable Integer Source # | |
Targetable Word8 Source # | |
Targetable () Source # | |
Targetable a => Targetable [a] Source # | |
Targetable a => Targetable (Maybe a) Source # | |
(Targetable a, Targetable b) => Targetable (Either a b) Source # | |
(Targetable a, Targetable b) => Targetable (a, b) Source # | |
(Targetable a, Targetable b, Targetable c) => Targetable (a, b, c) Source # | |
(Targetable a, Targetable b, Targetable c, Targetable d) => Targetable (a, b, c, d) Source # | |
data TargetOpts Source #
TargetOpts | |
|
monomorphic :: Name -> ExpQ #
Monomorphise an arbitrary property by defaulting all type variables to Integer
.
For example, if f
has type
then Ord
a => [a] -> [a]$(
has type monomorphic
'f)[
.Integer
] -> [Integer
]
If you want to use monomorphic
in the same file where you defined the
property, the same scoping problems pop up as in quickCheckAll
:
see the note there about return []
.