| Copyright | (C) 2017 ATS Advanced Telematic Systems GmbH |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Stevan Andjelkovic <stevan.andjelkovic@strath.ac.uk> |
| Stability | provisional |
| Portability | non-portable (GHC extensions) |
| Safe Haskell | None |
| Language | Haskell2010 |
Test.StateMachine
Description
The main module for state machine based testing, it contains combinators that help you build sequential and parallel properties.
Synopsis
- forAllCommands :: Testable prop => (Show (cmd Symbolic), Show (resp Symbolic), Show (model Symbolic)) => (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> Maybe Int -> (Commands cmd resp -> prop) -> Property
- existsCommands :: forall model cmd m resp prop. (Testable prop, Foldable resp) => (Show (model Symbolic), Show (cmd Symbolic), Show (resp Symbolic)) => StateMachine model cmd m resp -> [model Symbolic -> Gen (cmd Symbolic)] -> (Commands cmd resp -> prop) -> Property
- runCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadIO m) => StateMachine model cmd m resp -> Commands cmd resp -> PropertyM m (History cmd resp, model Concrete, Reason)
- prettyCommands :: (MonadIO m, ToExpr (model Concrete)) => (Show (cmd Concrete), Show (resp Concrete)) => StateMachine model cmd m resp -> History cmd resp -> Property -> PropertyM m ()
- prettyCommands' :: (MonadIO m, ToExpr (model Concrete), ToExpr tag) => (Show (cmd Concrete), Show (resp Concrete)) => StateMachine model cmd m resp -> ([Event model cmd resp Symbolic] -> [tag]) -> Commands cmd resp -> History cmd resp -> Property -> PropertyM m ()
- checkCommandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> Property -> Property
- coverCommandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> Property -> Property
- commandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> [(String, Int)]
- commandNamesInOrder :: forall cmd resp. CommandNames cmd => Commands cmd resp -> [String]
- saveCommands :: (Show (cmd Symbolic), Show (resp Symbolic)) => FilePath -> Commands cmd resp -> Property -> Property
- runSavedCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadIO m) => (Read (cmd Symbolic), Read (resp Symbolic)) => StateMachine model cmd m resp -> FilePath -> PropertyM m (Commands cmd resp, History cmd resp, model Concrete, Reason)
- showLabelledExamples :: (Show tag, Show (model Symbolic)) => (Show (cmd Symbolic), Show (resp Symbolic)) => (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> ([Event model cmd resp Symbolic] -> [tag]) -> IO ()
- showLabelledExamples' :: (Show tag, Show (model Symbolic)) => (Show (cmd Symbolic), Show (resp Symbolic)) => (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> Maybe Int -> Int -> ([Event model cmd resp Symbolic] -> [tag]) -> (tag -> Bool) -> IO ()
- noCleanup :: Monad m => model Concrete -> m ()
- forAllParallelCommands :: Testable prop => (Show (cmd Symbolic), Show (resp Symbolic), Show (model Symbolic)) => (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> Maybe Int -> (ParallelCommands cmd resp -> prop) -> Property
- forAllNParallelCommands :: Testable prop => (Show (cmd Symbolic), Show (resp Symbolic), Show (model Symbolic)) => (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> Int -> (NParallelCommands cmd resp -> prop) -> Property
- runNParallelCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => StateMachine model cmd m resp -> NParallelCommands cmd resp -> PropertyM m [(History cmd resp, Logic)]
- runParallelCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => StateMachine model cmd m resp -> ParallelCommands cmd resp -> PropertyM m [(History cmd resp, Logic)]
- runParallelCommands' :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => StateMachine model cmd m resp -> (cmd Concrete -> resp Concrete) -> ParallelCommands cmd resp -> PropertyM m [(History cmd resp, Logic)]
- runParallelCommandsNTimes :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => Int -> StateMachine model cmd m resp -> ParallelCommands cmd resp -> PropertyM m [(History cmd resp, Logic)]
- runNParallelCommandsNTimes' :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => Int -> StateMachine model cmd m resp -> (cmd Concrete -> resp Concrete) -> NParallelCommands cmd resp -> PropertyM m [(History cmd resp, Logic)]
- runParallelCommandsNTimes' :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => Int -> StateMachine model cmd m resp -> (cmd Concrete -> resp Concrete) -> ParallelCommands cmd resp -> PropertyM m [(History cmd resp, Logic)]
- runNParallelCommandsNTimes :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => Int -> StateMachine model cmd m resp -> NParallelCommands cmd resp -> PropertyM m [(History cmd resp, Logic)]
- prettyNParallelCommands :: (Show (cmd Concrete), Show (resp Concrete)) => MonadIO m => Foldable cmd => NParallelCommands cmd resp -> [(History cmd resp, Logic)] -> PropertyM m ()
- prettyParallelCommands :: (Show (cmd Concrete), Show (resp Concrete)) => MonadIO m => Foldable cmd => ParallelCommands cmd resp -> [(History cmd resp, Logic)] -> PropertyM m ()
- prettyParallelCommandsWithOpts :: (MonadIO m, Foldable cmd) => (Show (cmd Concrete), Show (resp Concrete)) => ParallelCommands cmd resp -> Maybe GraphOptions -> [(History cmd resp, Logic)] -> PropertyM m ()
- prettyNParallelCommandsWithOpts :: (Show (cmd Concrete), Show (resp Concrete)) => MonadIO m => Foldable cmd => NParallelCommands cmd resp -> Maybe GraphOptions -> [(History cmd resp, Logic)] -> PropertyM m ()
- checkCommandNamesParallel :: forall cmd resp t. Foldable t => CommandNames cmd => ParallelCommandsF t cmd resp -> Property -> Property
- coverCommandNamesParallel :: forall cmd resp t. Foldable t => CommandNames cmd => ParallelCommandsF t cmd resp -> Property -> Property
- commandNamesParallel :: forall cmd resp t. Foldable t => CommandNames cmd => ParallelCommandsF t cmd resp -> [(String, Int)]
- data StateMachine model cmd m resp = StateMachine (forall r. model r) (forall r. (Show1 r, Ord1 r) => model r -> cmd r -> resp r -> model r) (model Symbolic -> cmd Symbolic -> Logic) (model Concrete -> cmd Concrete -> resp Concrete -> Logic) (Maybe (model Concrete -> Logic)) (model Symbolic -> Maybe (Gen (cmd Symbolic))) (model Symbolic -> cmd Symbolic -> [cmd Symbolic]) (cmd Concrete -> m (resp Concrete)) (model Symbolic -> cmd Symbolic -> GenSym (resp Symbolic)) (model Concrete -> m ())
- data Concrete a
- data Symbolic a
- data Reference a r
- concrete :: Reference a Concrete -> a
- reference :: Typeable a => a -> Reference a Concrete
- newtype Opaque a = Opaque {
- unOpaque :: a
- opaque :: Reference (Opaque a) Concrete -> a
- data Reason
- data GenSym a
- genSym :: Typeable a => GenSym (Reference a Symbolic)
- class CommandNames (cmd :: k -> Type) where
- module Test.StateMachine.Logic
- module Test.StateMachine.Markov
- class ToExpr a
- toExpr :: ToExpr a => a -> Expr
Sequential property combinators
Arguments
| :: (Testable prop, Foldable resp) | |
| => (Show (model Symbolic), Show (cmd Symbolic), Show (resp Symbolic)) | |
| => StateMachine model cmd m resp | |
| -> [model Symbolic -> Gen (cmd Symbolic)] | Generators. |
| -> (Commands cmd resp -> prop) | Predicate. |
| -> Property |
Generate commands from a list of generators.
runCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadIO m) => StateMachine model cmd m resp -> Commands cmd resp -> PropertyM m (History cmd resp, model Concrete, Reason) Source #
prettyCommands :: (MonadIO m, ToExpr (model Concrete)) => (Show (cmd Concrete), Show (resp Concrete)) => StateMachine model cmd m resp -> History cmd resp -> Property -> PropertyM m () Source #
prettyCommands' :: (MonadIO m, ToExpr (model Concrete), ToExpr tag) => (Show (cmd Concrete), Show (resp Concrete)) => StateMachine model cmd m resp -> ([Event model cmd resp Symbolic] -> [tag]) -> Commands cmd resp -> History cmd resp -> Property -> PropertyM m () Source #
Variant of prettyCommands that also prints the tags covered by each
command.
checkCommandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> Property -> Property Source #
Print the percentage of each command used. The prefix check is an unfortunate remaining for backwards compatibility.
coverCommandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> Property -> Property Source #
Fail if some commands have not been executed.
commandNames :: forall cmd resp. CommandNames cmd => Commands cmd resp -> [(String, Int)] Source #
commandNamesInOrder :: forall cmd resp. CommandNames cmd => Commands cmd resp -> [String] Source #
saveCommands :: (Show (cmd Symbolic), Show (resp Symbolic)) => FilePath -> Commands cmd resp -> Property -> Property Source #
runSavedCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadIO m) => (Read (cmd Symbolic), Read (resp Symbolic)) => StateMachine model cmd m resp -> FilePath -> PropertyM m (Commands cmd resp, History cmd resp, model Concrete, Reason) Source #
showLabelledExamples :: (Show tag, Show (model Symbolic)) => (Show (cmd Symbolic), Show (resp Symbolic)) => (Traversable cmd, Foldable resp) => StateMachine model cmd m resp -> ([Event model cmd resp Symbolic] -> [tag]) -> IO () Source #
showLabelledExamples' Source #
Arguments
| :: (Show tag, Show (model Symbolic)) | |
| => (Show (cmd Symbolic), Show (resp Symbolic)) | |
| => (Traversable cmd, Foldable resp) | |
| => StateMachine model cmd m resp | |
| -> Maybe Int | Seed |
| -> Int | Number of tests to run to find examples |
| -> ([Event model cmd resp Symbolic] -> [tag]) | |
| -> (tag -> Bool) | Tag filter (can be |
| -> IO () |
Show minimal examples for each of the generated tags.
Parallel property combinators
forAllParallelCommands Source #
Arguments
| :: Testable prop | |
| => (Show (cmd Symbolic), Show (resp Symbolic), Show (model Symbolic)) | |
| => (Traversable cmd, Foldable resp) | |
| => StateMachine model cmd m resp | |
| -> Maybe Int | |
| -> (ParallelCommands cmd resp -> prop) | Predicate. |
| -> Property |
forAllNParallelCommands Source #
Arguments
| :: Testable prop | |
| => (Show (cmd Symbolic), Show (resp Symbolic), Show (model Symbolic)) | |
| => (Traversable cmd, Foldable resp) | |
| => StateMachine model cmd m resp | |
| -> Int | Number of threads |
| -> (NParallelCommands cmd resp -> prop) | Predicate. |
| -> Property |
runNParallelCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => StateMachine model cmd m resp -> NParallelCommands cmd resp -> PropertyM m [(History cmd resp, Logic)] Source #
runParallelCommands :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => StateMachine model cmd m resp -> ParallelCommands cmd resp -> PropertyM m [(History cmd resp, Logic)] Source #
runParallelCommands' :: (Show (cmd Concrete), Show (resp Concrete)) => (Traversable cmd, Foldable resp) => (MonadMask m, MonadUnliftIO m) => StateMachine model cmd m resp -> (cmd Concrete -> resp Concrete) -> ParallelCommands cmd resp -> PropertyM m [(History cmd resp, Logic)] Source #
runParallelCommandsNTimes Source #
Arguments
| :: (Show (cmd Concrete), Show (resp Concrete)) | |
| => (Traversable cmd, Foldable resp) | |
| => (MonadMask m, MonadUnliftIO m) | |
| => Int | How many times to execute the parallel program. |
| -> StateMachine model cmd m resp | |
| -> ParallelCommands cmd resp | |
| -> PropertyM m [(History cmd resp, Logic)] |
runNParallelCommandsNTimes' Source #
Arguments
| :: (Show (cmd Concrete), Show (resp Concrete)) | |
| => (Traversable cmd, Foldable resp) | |
| => (MonadMask m, MonadUnliftIO m) | |
| => Int | How many times to execute the parallel program. |
| -> StateMachine model cmd m resp | |
| -> (cmd Concrete -> resp Concrete) | |
| -> NParallelCommands cmd resp | |
| -> PropertyM m [(History cmd resp, Logic)] |
runParallelCommandsNTimes' Source #
Arguments
| :: (Show (cmd Concrete), Show (resp Concrete)) | |
| => (Traversable cmd, Foldable resp) | |
| => (MonadMask m, MonadUnliftIO m) | |
| => Int | How many times to execute the parallel program. |
| -> StateMachine model cmd m resp | |
| -> (cmd Concrete -> resp Concrete) | |
| -> ParallelCommands cmd resp | |
| -> PropertyM m [(History cmd resp, Logic)] |
runNParallelCommandsNTimes Source #
Arguments
| :: (Show (cmd Concrete), Show (resp Concrete)) | |
| => (Traversable cmd, Foldable resp) | |
| => (MonadMask m, MonadUnliftIO m) | |
| => Int | How many times to execute the parallel program. |
| -> StateMachine model cmd m resp | |
| -> NParallelCommands cmd resp | |
| -> PropertyM m [(History cmd resp, Logic)] |
prettyParallelCommandsWithOpts Source #
Arguments
| :: (MonadIO m, Foldable cmd) | |
| => (Show (cmd Concrete), Show (resp Concrete)) | |
| => ParallelCommands cmd resp | |
| -> Maybe GraphOptions | |
| -> [(History cmd resp, Logic)] | Output of |
| -> PropertyM m () |
Takes the output of parallel program runs and pretty prints a counterexample if any of the runs fail.
prettyNParallelCommandsWithOpts Source #
Arguments
| :: (Show (cmd Concrete), Show (resp Concrete)) | |
| => MonadIO m | |
| => Foldable cmd | |
| => NParallelCommands cmd resp | |
| -> Maybe GraphOptions | |
| -> [(History cmd resp, Logic)] | Output of |
| -> PropertyM m () |
Takes the output of parallel program runs and pretty prints a counterexample if any of the runs fail.
checkCommandNamesParallel :: forall cmd resp t. Foldable t => CommandNames cmd => ParallelCommandsF t cmd resp -> Property -> Property Source #
Print the percentage of each command used. The prefix check is an unfortunate remaining for backwards compatibility.
coverCommandNamesParallel :: forall cmd resp t. Foldable t => CommandNames cmd => ParallelCommandsF t cmd resp -> Property -> Property Source #
Fail if some commands have not been executed.
commandNamesParallel :: forall cmd resp t. Foldable t => CommandNames cmd => ParallelCommandsF t cmd resp -> [(String, Int)] Source #
Types
data StateMachine model cmd m resp Source #
Constructors
| StateMachine (forall r. model r) (forall r. (Show1 r, Ord1 r) => model r -> cmd r -> resp r -> model r) (model Symbolic -> cmd Symbolic -> Logic) (model Concrete -> cmd Concrete -> resp Concrete -> Logic) (Maybe (model Concrete -> Logic)) (model Symbolic -> Maybe (Gen (cmd Symbolic))) (model Symbolic -> cmd Symbolic -> [cmd Symbolic]) (cmd Concrete -> m (resp Concrete)) (model Symbolic -> cmd Symbolic -> GenSym (resp Symbolic)) (model Concrete -> m ()) |
Instances
| Eq1 Concrete Source # | |
| Ord1 Concrete Source # | |
Defined in Test.StateMachine.Types.References | |
| Show1 Concrete Source # | |
| Show a => Show (Concrete a) Source # | |
| ToExpr a => ToExpr (Concrete a) Source # | |
Defined in Test.StateMachine.Types.References | |
| (ToExpr (MockState t), All (And ToExpr (Compose ToExpr (MockHandle t))) (RealHandles t)) => ToExpr (Model t Concrete) Source # | |
| All (And ToExpr (Compose ToExpr (MockHandle t))) (RealHandles t) => ToExpr (Refss t Concrete) Source # | |
| (ToExpr a, ToExpr (MockHandle t a)) => ToExpr (Refs t Concrete a) Source # | |
Instances
| Eq1 Symbolic Source # | |
| Ord1 Symbolic Source # | |
Defined in Test.StateMachine.Types.References | |
| Show1 Symbolic Source # | |
| Eq (Symbolic a) Source # | |
| Ord (Symbolic a) Source # | |
Defined in Test.StateMachine.Types.References | |
| Typeable a => Read (Symbolic a) Source # | |
| Show (Symbolic a) Source # | |
| ToExpr a => ToExpr (Symbolic a) Source # | |
Defined in Test.StateMachine.Types.References | |
| Typeable a => Read (Reference a Symbolic) Source # | |
Instances
| Traversable (Reference a :: (Type -> Type) -> Type) Source # | |
Defined in Test.StateMachine.Types.References | |
| Foldable (Reference a :: (Type -> Type) -> Type) Source # | |
| Functor (Reference a :: (Type -> Type) -> Type) Source # | |
| (Eq a, Eq1 r) => Eq (Reference a r) Source # | |
| (Ord a, Ord1 r) => Ord (Reference a r) Source # | |
Defined in Test.StateMachine.Types.References Methods compare :: Reference a r -> Reference a r -> Ordering # (<) :: Reference a r -> Reference a r -> Bool # (<=) :: Reference a r -> Reference a r -> Bool # (>) :: Reference a r -> Reference a r -> Bool # (>=) :: Reference a r -> Reference a r -> Bool # | |
| Typeable a => Read (Reference a Symbolic) Source # | |
| (Show1 r, Show a) => Show (Reference a r) Source # | |
| Generic (Reference a r) Source # | |
| ToExpr (r a) => ToExpr (Reference a r) Source # | |
Defined in Test.StateMachine.Types.References | |
| type Rep (Reference a r) Source # | |
Defined in Test.StateMachine.Types.References | |
class CommandNames (cmd :: k -> Type) where Source #
The names of all possible commands
This is used for things like tagging, coverage checking, etc.
Minimal complete definition
Nothing
Methods
cmdName :: cmd r -> String Source #
Name of this particular command
cmdNames :: Proxy (cmd r) -> [String] Source #
Name of all possible commands
cmdName :: (Generic1 cmd, CommandNames (Rep1 cmd)) => cmd r -> String Source #
Name of this particular command
cmdNames :: forall r. CommandNames (Rep1 cmd) => Proxy (cmd r) -> [String] Source #
Name of all possible commands
Instances
| CommandNames (U1 :: k -> Type) Source # | |
| CommandNames f => CommandNames (Rec1 f :: k -> Type) Source # | |
| (CommandNames f, CommandNames g) => CommandNames (f :*: g :: k -> Type) Source # | |
| (CommandNames f, CommandNames g) => CommandNames (f :+: g :: k -> Type) Source # | |
| CommandNames (K1 i c :: k -> Type) Source # | |
| CommandNames f => CommandNames (M1 S c f :: k -> Type) Source # | |
| CommandNames f => CommandNames (M1 D c f :: k -> Type) Source # | |
| Constructor c => CommandNames (M1 C c f :: k -> Type) Source # | |
module Test.StateMachine.Logic
module Test.StateMachine.Markov
Re-export
toExpr converts a Haskell value into
untyped Haskell-like syntax tree, Expr.
>>>toExpr ((1, Just 2) :: (Int, Maybe Int))App "_\215_" [App "1" [],App "Just" [App "2" []]]
Instances
| ToExpr Bool | |
Defined in Data.TreeDiff.Class | |
| ToExpr Char |
|
Defined in Data.TreeDiff.Class | |
| ToExpr Double | |
Defined in Data.TreeDiff.Class | |
| ToExpr Float | |
Defined in Data.TreeDiff.Class | |
| ToExpr Int | |
Defined in Data.TreeDiff.Class | |
| ToExpr Int8 | |
Defined in Data.TreeDiff.Class | |
| ToExpr Int16 | |
Defined in Data.TreeDiff.Class | |
| ToExpr Int32 | |
Defined in Data.TreeDiff.Class | |
| ToExpr Int64 | |
Defined in Data.TreeDiff.Class | |
| ToExpr Integer | |
Defined in Data.TreeDiff.Class | |
| ToExpr Natural | |
Defined in Data.TreeDiff.Class | |
| ToExpr Ordering | |
Defined in Data.TreeDiff.Class | |
| ToExpr Word | |
Defined in Data.TreeDiff.Class | |
| ToExpr Word8 | |
Defined in Data.TreeDiff.Class | |
| ToExpr Word16 | |
Defined in Data.TreeDiff.Class | |
| ToExpr Word32 | |
Defined in Data.TreeDiff.Class | |
| ToExpr Word64 | |
Defined in Data.TreeDiff.Class | |
| ToExpr () | |
Defined in Data.TreeDiff.Class | |
| ToExpr ByteString |
|
Defined in Data.TreeDiff.Class | |
| ToExpr ByteString |
|
Defined in Data.TreeDiff.Class | |
| ToExpr Scientific |
|
Defined in Data.TreeDiff.Class | |
| ToExpr Text |
|
Defined in Data.TreeDiff.Class | |
| ToExpr UTCTime | |
Defined in Data.TreeDiff.Class | |
| ToExpr Value | |
Defined in Data.TreeDiff.Class | |
| ToExpr Text |
|
Defined in Data.TreeDiff.Class | |
| ToExpr Void | |
Defined in Data.TreeDiff.Class | |
| ToExpr ShortByteString |
|
Defined in Data.TreeDiff.Class | |
| ToExpr IntSet | |
Defined in Data.TreeDiff.Class | |
| ToExpr Day |
|
Defined in Data.TreeDiff.Class | |
| ToExpr Expr | |
Defined in Data.TreeDiff.Class | |
| ToExpr UUID |
|
Defined in Data.TreeDiff.Class | |
| ToExpr Var Source # | |
Defined in Test.StateMachine.Types.References | |
| ToExpr a => ToExpr [a] | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Maybe a) | |
Defined in Data.TreeDiff.Class | |
| (ToExpr a, Integral a) => ToExpr (Ratio a) |
|
Defined in Data.TreeDiff.Class | |
| HasResolution a => ToExpr (Fixed a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Min a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Max a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (First a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Last a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Option a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (ZipList a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Identity a) |
|
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (First a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Last a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Dual a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Sum a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Product a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (NonEmpty a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr v => ToExpr (IntMap v) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Tree a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr v => ToExpr (Seq v) | |
Defined in Data.TreeDiff.Class | |
| ToExpr k => ToExpr (Set k) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Hashed a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Vector a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr k => ToExpr (HashSet k) | |
Defined in Data.TreeDiff.Class | |
| (ToExpr a, Unbox a) => ToExpr (Vector a) | |
Defined in Data.TreeDiff.Class | |
| (ToExpr a, Storable a) => ToExpr (Vector a) | |
Defined in Data.TreeDiff.Class | |
| (ToExpr a, Prim a) => ToExpr (Vector a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr (Opaque a) Source # | |
Defined in Test.StateMachine.Types.References | |
| ToExpr a => ToExpr (Concrete a) Source # | |
Defined in Test.StateMachine.Types.References | |
| ToExpr a => ToExpr (Symbolic a) Source # | |
Defined in Test.StateMachine.Types.References | |
| (ToExpr a, ToExpr b) => ToExpr (Either a b) | |
Defined in Data.TreeDiff.Class | |
| (ToExpr a, ToExpr b) => ToExpr (a, b) | |
Defined in Data.TreeDiff.Class | |
| (ToExpr k, ToExpr v) => ToExpr (HashMap k v) | |
Defined in Data.TreeDiff.Class | |
| (ToExpr k, ToExpr v) => ToExpr (Map k v) | |
Defined in Data.TreeDiff.Class | |
| ToExpr (Proxy a) | |
Defined in Data.TreeDiff.Class | |
| ToExpr (r a) => ToExpr (Reference a r) Source # | |
Defined in Test.StateMachine.Types.References | |
| (ToExpr (MockState t), All (And ToExpr (Compose ToExpr (MockHandle t))) (RealHandles t)) => ToExpr (Model t Concrete) Source # | |
| All (And ToExpr (Compose ToExpr (MockHandle t))) (RealHandles t) => ToExpr (Refss t Concrete) Source # | |
| (ToExpr a, ToExpr b, ToExpr c) => ToExpr (a, b, c) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Const a b) | |
Defined in Data.TreeDiff.Class | |
| ToExpr a => ToExpr (Tagged t a) | |
Defined in Data.TreeDiff.Class | |
| (ToExpr a, ToExpr (MockHandle t a)) => ToExpr (Refs t Concrete a) Source # | |
| (ToExpr a, ToExpr b, ToExpr c, ToExpr d) => ToExpr (a, b, c, d) | |
Defined in Data.TreeDiff.Class | |
| (ToExpr a, ToExpr b, ToExpr c, ToExpr d, ToExpr e) => ToExpr (a, b, c, d, e) | |
Defined in Data.TreeDiff.Class | |