quickcheck-state-machine-0.5.0: Test monadic programs using state machine based models

Copyright(C) 2017 Jacob Stanley
LicenseBSD-style (see the file LICENSE)
MaintainerStevan Andjelkovic <stevan.andjelkovic@here.com>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Test.StateMachine.Types.References

Description

This module contains reference related types. It's taken almost verbatim from the Hedgehog library.

Documentation

newtype Var Source #

Constructors

Var Int 
Instances
Eq Var Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

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

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

Ord Var Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Show Var Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Generic Var Source # 
Instance details

Defined in Test.StateMachine.Types.References

Associated Types

type Rep Var :: Type -> Type #

Methods

from :: Var -> Rep Var x #

to :: Rep Var x -> Var #

ToExpr Var Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

toExpr :: Var -> Expr #

listToExpr :: [Var] -> Expr #

type Rep Var Source # 
Instance details

Defined in Test.StateMachine.Types.References

type Rep Var = D1 (MetaData "Var" "Test.StateMachine.Types.References" "quickcheck-state-machine-0.5.0-EvtR9eyRN0z9VDBEE7rFU" True) (C1 (MetaCons "Var" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data Symbolic a where Source #

Constructors

Symbolic :: Typeable a => Var -> Symbolic a 
Instances
Eq1 Symbolic Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftEq :: (a -> b -> Bool) -> Symbolic a -> Symbolic b -> Bool #

Ord1 Symbolic Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftCompare :: (a -> b -> Ordering) -> Symbolic a -> Symbolic b -> Ordering #

Show1 Symbolic Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Symbolic a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Symbolic a] -> ShowS #

Eq (Symbolic a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

(==) :: Symbolic a -> Symbolic a -> Bool #

(/=) :: Symbolic a -> Symbolic a -> Bool #

Ord (Symbolic a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

compare :: Symbolic a -> Symbolic a -> Ordering #

(<) :: Symbolic a -> Symbolic a -> Bool #

(<=) :: Symbolic a -> Symbolic a -> Bool #

(>) :: Symbolic a -> Symbolic a -> Bool #

(>=) :: Symbolic a -> Symbolic a -> Bool #

max :: Symbolic a -> Symbolic a -> Symbolic a #

min :: Symbolic a -> Symbolic a -> Symbolic a #

Show (Symbolic a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

showsPrec :: Int -> Symbolic a -> ShowS #

show :: Symbolic a -> String #

showList :: [Symbolic a] -> ShowS #

ToExpr a => ToExpr (Symbolic a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

toExpr :: Symbolic a -> Expr #

listToExpr :: [Symbolic a] -> Expr #

data Concrete a where Source #

Constructors

Concrete :: Typeable a => a -> Concrete a 
Instances
Eq1 Concrete Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftEq :: (a -> b -> Bool) -> Concrete a -> Concrete b -> Bool #

Ord1 Concrete Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftCompare :: (a -> b -> Ordering) -> Concrete a -> Concrete b -> Ordering #

Show1 Concrete Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Concrete a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Concrete a] -> ShowS #

Show a => Show (Concrete a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

showsPrec :: Int -> Concrete a -> ShowS #

show :: Concrete a -> String #

showList :: [Concrete a] -> ShowS #

ToExpr a => ToExpr (Concrete a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

toExpr :: Concrete a -> Expr #

listToExpr :: [Concrete a] -> Expr #

data Reference a r Source #

Constructors

Reference (r a) 
Instances
Traversable (Reference a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

traverse :: Applicative f => (forall (a0 :: k). p a0 -> f (q a0)) -> Reference a p -> f (Reference a q) Source #

Foldable (Reference a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

foldMap :: Monoid m => (forall (x :: k). p x -> m) -> Reference a p -> m Source #

Functor (Reference a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

fmap :: (forall (x :: k). p x -> q x) -> Reference a p -> Reference a q Source #

(Eq a, Eq1 r) => Eq (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

(==) :: Reference a r -> Reference a r -> Bool #

(/=) :: Reference a r -> Reference a r -> Bool #

(Ord a, Ord1 r) => Ord (Reference a r) Source # 
Instance details

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 #

max :: Reference a r -> Reference a r -> Reference a r #

min :: Reference a r -> Reference a r -> Reference a r #

(Show1 r, Show a) => Show (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

showsPrec :: Int -> Reference a r -> ShowS #

show :: Reference a r -> String #

showList :: [Reference a r] -> ShowS #

Generic (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Associated Types

type Rep (Reference a r) :: Type -> Type #

Methods

from :: Reference a r -> Rep (Reference a r) x #

to :: Rep (Reference a r) x -> Reference a r #

ToExpr (r a) => ToExpr (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

toExpr :: Reference a r -> Expr #

listToExpr :: [Reference a r] -> Expr #

GConName1 (Reference a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Test.StateMachine.ConstructorName

type Rep (Reference a r) Source # 
Instance details

Defined in Test.StateMachine.Types.References

type Rep (Reference a r) = D1 (MetaData "Reference" "Test.StateMachine.Types.References" "quickcheck-state-machine-0.5.0-EvtR9eyRN0z9VDBEE7rFU" False) (C1 (MetaCons "Reference" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (r a))))

newtype Opaque a Source #

Constructors

Opaque a 
Instances
Eq a => Eq (Opaque a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

(==) :: Opaque a -> Opaque a -> Bool #

(/=) :: Opaque a -> Opaque a -> Bool #

Ord a => Ord (Opaque a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

compare :: Opaque a -> Opaque a -> Ordering #

(<) :: Opaque a -> Opaque a -> Bool #

(<=) :: Opaque a -> Opaque a -> Bool #

(>) :: Opaque a -> Opaque a -> Bool #

(>=) :: Opaque a -> Opaque a -> Bool #

max :: Opaque a -> Opaque a -> Opaque a #

min :: Opaque a -> Opaque a -> Opaque a #

Show (Opaque a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

showsPrec :: Int -> Opaque a -> ShowS #

show :: Opaque a -> String #

showList :: [Opaque a] -> ShowS #

ToExpr (Opaque a) Source # 
Instance details

Defined in Test.StateMachine.Types.References

Methods

toExpr :: Opaque a -> Expr #

listToExpr :: [Opaque a] -> Expr #