symbiote-0.0.0: Data serialization, communication, and operation verification implementation

Safe HaskellNone
LanguageHaskell2010

Test.Serialization.Symbiote

Description

The project operates as follows:

Given two peers A and B and some communications transport T (utilizing a serialization format S), and a data type Q with some set of operations on that data type Op_Q, the following functions / procedures are assumed:

tAB: the function communicates some data in S from peer A to peer B tBA: the function communicates some data in S from peer B to peer A encode :: Q -> S decode :: S -> Q -- disregarding error handling

And the following property should exist, from peer A's perspective:

forall f in Op_Q, q in Q. f q == decode (tBA (f (tAB (encode q)))

where the left invocation of f occurs in peer A, and the right invocation occurs in peer B.

Synopsis

Documentation

class SymbioteOperation a where Source #

Associated Types

data Operation a :: * Source #

Methods

perform :: Operation a -> a -> a Source #

class SymbioteOperation a => Symbiote a s where Source #

A type and operation set over a serialization format

Methods

encode :: a -> s Source #

decode :: s -> Maybe a Source #

encodeOp :: Operation a -> s Source #

decodeOp :: s -> Maybe (Operation a) Source #

newtype EitherOp a Source #

The most trivial serialization medium for any a.

Constructors

EitherOp (Either a (Operation a)) 
Instances
SymbioteOperation a => Symbiote a (EitherOp a) Source # 
Instance details

Defined in Test.Serialization.Symbiote

(Eq a, Eq (Operation a)) => Eq (EitherOp a) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

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

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

(Show a, Show (Operation a)) => Show (EitherOp a) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

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

show :: EitherOp a -> String #

showList :: [EitherOp a] -> ShowS #

data Topic Source #

Unique name of a type, for a suite of tests

Instances
Eq Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

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

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

Ord Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

compare :: Topic -> Topic -> Ordering #

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

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

(>) :: Topic -> Topic -> Bool #

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

max :: Topic -> Topic -> Topic #

min :: Topic -> Topic -> Topic #

Show Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

showsPrec :: Int -> Topic -> ShowS #

show :: Topic -> String #

showList :: [Topic] -> ShowS #

IsString Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

fromString :: String -> Topic #

type SymbioteT s m = ReaderT Bool (StateT (Map Topic (SymbioteState s)) m) Source #

register Source #

Arguments

:: Arbitrary a 
=> Arbitrary (Operation a) 
=> Symbiote a s 
=> Eq a 
=> MonadIO m 
=> Topic 
-> Int

Max size

-> Proxy a 
-> SymbioteT s m () 

Register a topic in the test suite

firstPeer Source #

Arguments

:: MonadIO m 
=> Show s 
=> (First s -> m ())

Encode and send first messages

-> m (Second s)

Receive and decode second messages

-> (Topic -> m ())

Report when Successful

-> (Failure Second s -> m ())

Report when Failed

-> (Topic -> Float -> m ())

Report on Progress

-> SymbioteT s m () 
-> m () 

secondPeer Source #

Arguments

:: MonadIO m 
=> Show s 
=> (Second s -> m ())

Encode and send second messages

-> m (First s)

Receive and decode first messages

-> (Topic -> m ())

Report when Successful

-> (Failure First s -> m ())

Report when Failed

-> (Topic -> Float -> m ())

Report on Progress

-> SymbioteT s m () 
-> m () 

data First s Source #

Messages sent by the first peer

Instances
Eq s => Eq (First s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

(==) :: First s -> First s -> Bool #

(/=) :: First s -> First s -> Bool #

Show s => Show (First s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

showsPrec :: Int -> First s -> ShowS #

show :: First s -> String #

showList :: [First s] -> ShowS #

data Second s Source #

Messages sent by the second peer

Constructors

BadTopics (Map Topic Int)

Second's available topics with identical gen sizes

Start 
SecondOperating 
SecondGenerating 
Instances
Eq s => Eq (Second s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

(==) :: Second s -> Second s -> Bool #

(/=) :: Second s -> Second s -> Bool #

Show s => Show (Second s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

showsPrec :: Int -> Second s -> ShowS #

show :: Second s -> String #

showList :: [Second s] -> ShowS #

data Generating s Source #

Messages sent by a peer during their generating phase

Constructors

Generated 

Fields

BadResult s

Expected value

YourTurn 
ImFinished 
GeneratingNoParseOperated s 
Instances
Eq s => Eq (Generating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

(==) :: Generating s -> Generating s -> Bool #

(/=) :: Generating s -> Generating s -> Bool #

Show s => Show (Generating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

data Operating s Source #

Messages sent by a peer during their operating phase

Constructors

Operated s

Serialized value after operation

OperatingNoParseValue s 
OperatingNoParseOperation s 
Instances
Eq s => Eq (Operating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

(==) :: Operating s -> Operating s -> Bool #

(/=) :: Operating s -> Operating s -> Bool #

Show s => Show (Operating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

defaultSuccess :: Topic -> IO () Source #

Via putStrLn

defaultFailure :: Show (them s) => Show s => Failure them s -> IO () Source #

Via putStrLn

defaultProgress :: Topic -> Float -> IO () Source #

Via putStrLn

nullProgress :: Topic -> Float -> IO () Source #

Do nothing

simpleTest :: MonadBaseControl IO m => MonadIO m => Show s => SymbioteT s m () -> m () Source #

Prints to stdout and uses a local channel for a sanity-check - doesn't serialize.