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

Copyright(C) 2017 ATS Advanced Telematic Systems GmbH
LicenseBSD-style (see the file LICENSE)
MaintainerStevan Andjelkovic <stevan@advancedtelematic.com>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Test.StateMachine.Internal.Types

Description

This module exports some types that are used internally by the library.

Synopsis

Documentation

data IntRef Source #

An internal (or integer) reference consists of a reference and a process id.

Constructors

IntRef Ref Pid 

newtype Pid Source #

A process id is merely a natural number that keeps track of which thread the reference comes from. In the sequential case the process id is always 0. Likewise the sequential prefix of a parallel program also has process id 0, while the left suffix has process id 1, and then right suffix has process id 2.

Constructors

Pid Int 

Instances

Eq Pid Source # 

Methods

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

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

Num Pid Source # 

Methods

(+) :: Pid -> Pid -> Pid #

(-) :: Pid -> Pid -> Pid #

(*) :: Pid -> Pid -> Pid #

negate :: Pid -> Pid #

abs :: Pid -> Pid #

signum :: Pid -> Pid #

fromInteger :: Integer -> Pid #

Ord Pid Source # 

Methods

compare :: Pid -> Pid -> Ordering #

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

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

(>) :: Pid -> Pid -> Bool #

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

max :: Pid -> Pid -> Pid #

min :: Pid -> Pid -> Pid #

Read Pid Source # 
Show Pid Source # 

Methods

showsPrec :: Int -> Pid -> ShowS #

show :: Pid -> String #

showList :: [Pid] -> ShowS #

newtype Ref Source #

A reference is natural number.

Constructors

Ref Int 

Instances

Eq Ref Source # 

Methods

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

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

Num Ref Source # 

Methods

(+) :: Ref -> Ref -> Ref #

(-) :: Ref -> Ref -> Ref #

(*) :: Ref -> Ref -> Ref #

negate :: Ref -> Ref #

abs :: Ref -> Ref #

signum :: Ref -> Ref #

fromInteger :: Integer -> Ref #

Ord Ref Source # 

Methods

compare :: Ref -> Ref -> Ordering #

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

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

(>) :: Ref -> Ref -> Bool #

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

max :: Ref -> Ref -> Ref #

min :: Ref -> Ref -> Ref #

Read Ref Source # 
Show Ref Source # 

Methods

showsPrec :: Int -> Ref -> ShowS #

show :: Ref -> String #

showList :: [Ref] -> ShowS #

type ConstIntRef = ConstSym1 IntRef Source #

Type-level function that constantly returns an internal reference.

data IntRefed f where Source #

Internal untyped commands.

Constructors

IntRefed :: (Show (GetResponse_ resp), Typeable (Response_ ConstIntRef resp), Typeable resp) => f ConstIntRef resp -> MayResponse_ ConstIntRef resp -> IntRefed f 

Instances

(IxFunctor (Response ix) ix cmd, ShowCmd ix cmd, HasResponse ix (TyFun ix Type -> Type) cmd) => Show (IntRefed ix cmd) Source # 

Methods

showsPrec :: Int -> IntRefed ix cmd -> ShowS #

show :: IntRefed ix cmd -> String #

showList :: [IntRefed ix cmd] -> ShowS #

data Fork a Source #

Forks are used to represent parallel programs. They have a sequential prefix (the middle argument of the constructor), and two parallel suffixes (the left- and right-most argument of the constructor).

Constructors

Fork a a a 

Instances

Functor Fork Source # 

Methods

fmap :: (a -> b) -> Fork a -> Fork b #

(<$) :: a -> Fork b -> Fork a #

Eq a => Eq (Fork a) Source # 

Methods

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

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

Ord a => Ord (Fork a) Source # 

Methods

compare :: Fork a -> Fork a -> Ordering #

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

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

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

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

max :: Fork a -> Fork a -> Fork a #

min :: Fork a -> Fork a -> Fork a #

Read a => Read (Fork a) Source # 
Show a => Show (Fork a) Source # 

Methods

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

show :: Fork a -> String #

showList :: [Fork a] -> ShowS #

Pretty a => Pretty (Fork a) Source # 

Methods

pretty :: Fork a -> Doc #

prettyList :: [Fork a] -> Doc #

showResponse_ :: Show (GetResponse_ resp) => SResponse ix resp -> Response_ ConstIntRef resp -> String Source #

Show function for Response_.

type family MayResponse_ (refs :: TyFun ix k -> Type) (resp :: Response ix) :: k where ... Source #

Type-level function that maybe returns a reference.

Equations

MayResponse_ refs (Response t) = () 
MayResponse_ refs (Reference i) = refs @@ i