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

Copyright(c) 2019 Athan Clark
LicenseBSD-3-Style
Maintainerathan.clark@gmail.com
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Test.Serialization.Symbiote.Core

Description

This module defines the machinery of any topic's state machine:

  • agnostic for whatever type or operation you're testing
  • doesn't try to define the stuff that orchestrates multiple topics operating together
  • doesn't specify how the protocol actually looks with respect to the messages sent between the peers
Synopsis

Documentation

class SymbioteOperation a o | a -> o where Source #

A type-level relation between a type and appropriate, testable operations on that type.

Associated Types

data Operation a :: * Source #

An enumerated type of operations on a that result in o.

Methods

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

Apply the Operation to a, to get an o.

Instances
(Fractional a, Eq a) => SymbioteOperation (AbidesField a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesField a) :: Type Source #

(Num a, Eq a) => SymbioteOperation (AbidesEuclideanRing a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesEuclideanRing a) :: Type Source #

(Fractional a, Eq a) => SymbioteOperation (AbidesDivisionRing a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesDivisionRing a) :: Type Source #

(Num a, Eq a) => SymbioteOperation (AbidesCommutativeRing a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesCommutativeRing a) :: Type Source #

(Num a, Eq a) => SymbioteOperation (AbidesRing a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesRing a) :: Type Source #

(Num a, Eq a) => SymbioteOperation (AbidesSemiring a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesSemiring a) :: Type Source #

(Enum a, Ord a) => SymbioteOperation (AbidesEnum a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesEnum a) :: Type Source #

Ord a => SymbioteOperation (AbidesOrd a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesOrd a) :: Type Source #

Eq a => SymbioteOperation (AbidesEq a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesEq a) :: Type Source #

(Monoid a, Eq a) => SymbioteOperation (AbidesMonoid a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesMonoid a) :: Type Source #

(Semigroup a, Eq a) => SymbioteOperation (AbidesSemigroup a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesSemigroup a) :: Type Source #

class SymbioteOperation a o => Symbiote a o s | a -> o where Source #

A serialization format for a particular type, and serialized data type.

Methods

encode :: a -> s Source #

decode :: s -> Maybe a Source #

encodeOut :: Proxy a -> o -> s Source #

Needs a reference to a because the fundep is only one direction (i.e. only one output defined per input, but could be used elsewhere)

decodeOut :: Proxy a -> s -> Maybe o Source #

Needs a reference to a because the fundep is only one direction

encodeOp :: Operation a -> s Source #

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

Instances
(Serialize a, Serialize o, Serialize (Operation a), SymbioteOperation a o) => Symbiote a o ByteString Source # 
Instance details

Defined in Test.Serialization.Symbiote.Cereal.Lazy

(Serialize a, Serialize o, Serialize (Operation a), SymbioteOperation a o) => Symbiote a o ByteString Source # 
Instance details

Defined in Test.Serialization.Symbiote.Cereal

(ToJSON a, FromJSON a, ToJSON o, FromJSON o, ToJSON (Operation a), FromJSON (Operation a), SymbioteOperation a o) => Symbiote a o Value Source # 
Instance details

Defined in Test.Serialization.Symbiote.Aeson

SymbioteOperation a o => Symbiote a o (SimpleSerialization a o) Source # 
Instance details

Defined in Test.Serialization.Symbiote

newtype Topic Source #

Unique name of a type, for a suite of tests. Ref - Topic.

Constructors

Topic Text 
Instances
Eq Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

Methods

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

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

Ord Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

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.Core

Methods

showsPrec :: Int -> Topic -> ShowS #

show :: Topic -> String #

showList :: [Topic] -> ShowS #

IsString Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

Methods

fromString :: String -> Topic #

Arbitrary Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

Methods

arbitrary :: Gen Topic #

shrink :: Topic -> [Topic] #

ToJSON Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

ToJSONKey Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

FromJSON Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

FromJSONKey Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

Serialize Topic Source #

Serialized as a String32 in the symbiotic-data standard.

Instance details

Defined in Test.Serialization.Symbiote.Core

Methods

put :: Putter Topic #

get :: Get Topic #

data SymbioteProtocol a s Source #

The state-machine representation for a particular topic, identical for each peer. As the protocol progresses and messages are passed, and values are generated, this value will change over time, and is unique for each topic.

Constructors

MeGenerated

"I'm generating a value"

Fields

ThemGenerating

"They're generating a value"

Fields

  • themGen :: Maybe (s, s)

    Remotely generated value and operation - might not exist due to the need for the remote party to send the a and Operation values.

NotStarted

The topic's generation / operation exchange hasn't started for either peer

Finished

The topic's generation / operation exchange has completed, and is currently being processed on another topic, or the whole suite is finished for all topics.

data SymbioteGeneration a s Source #

Protocol state, with amended "current generation value" information

Constructors

SymbioteGeneration 

Fields

newGeneration :: SymbioteGeneration a s Source #

The initial state for any topic's state machine.

data SymbioteState a o s Source #

Internal existential state of a registered topic, with fields explicitly storing a type's normally typeclass-specified facilities.

Constructors

SymbioteState 

Fields

data ExistsSymbiote s Source #

A custom existential quantifier, which places additional typeclass constraints on the a and o variables of SymbioteState, leaving only s as the globally visible type variable - the "serialization" medium.

Constructors

(Arbitrary a, Arbitrary (Operation a), Symbiote a o s, Eq o) => ExistsSymbiote (SymbioteState a o s) 

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

Builder for the total set of topics supported by this peer.

runSymbioteT Source #

Arguments

:: Monad m 
=> SymbioteT s m () 
-> Bool

Is this the first peer to initiate the protocol?

-> m (Map Topic (ExistsSymbiote s)) 

Get the set of topics from the builder.

data GenerateSymbiote s Source #

Used internally - attempt generating a value and operation for a specific topic, by using the mechanics defined in the protocol's stored state and existential typeclass facilities.

Constructors

DoneGenerating

Can't generate any more values, and "is finished"

GeneratedSymbiote

Generated a value and operation, as serialized values

generateSymbiote :: forall s m. MonadIO m => ExistsSymbiote s -> m (GenerateSymbiote s) Source #

Given an existentially stored topic state, attempt to generate a value and operation for that topic's type.

getProgress :: MonadIO m => ExistsSymbiote s -> m Float Source #

The current "progress" or "percent complete" of the topic - the current size divided by the maxSize.