ron-0.12: RON
Safe HaskellNone
LanguageHaskell2010

RON.Types

Contents

Description

RON model types

Synopsis

Documentation

data Atom Source #

Atom — a payload element

Instances

Instances details
Eq Atom Source # 
Instance details

Defined in RON.Types

Methods

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

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

Data Atom Source # 
Instance details

Defined in RON.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Atom -> c Atom #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Atom #

toConstr :: Atom -> Constr #

dataTypeOf :: Atom -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Atom) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Atom) #

gmapT :: (forall b. Data b => b -> b) -> Atom -> Atom #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r #

gmapQ :: (forall d. Data d => d -> u) -> Atom -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Atom -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Atom -> m Atom #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Atom -> m Atom #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Atom -> m Atom #

Show Atom Source # 
Instance details

Defined in RON.Types

Methods

showsPrec :: Int -> Atom -> ShowS #

show :: Atom -> String #

showList :: [Atom] -> ShowS #

IsString Atom Source # 
Instance details

Defined in RON.Types

Methods

fromString :: String -> Atom #

Generic Atom Source # 
Instance details

Defined in RON.Types

Associated Types

type Rep Atom :: Type -> Type #

Methods

from :: Atom -> Rep Atom x #

to :: Rep Atom x -> Atom #

Hashable Atom Source # 
Instance details

Defined in RON.Types

Methods

hashWithSalt :: Int -> Atom -> Int #

hash :: Atom -> Int #

type Rep Atom Source # 
Instance details

Defined in RON.Types

data ClosedOp Source #

Closed op

Constructors

ClosedOp 

Fields

Instances

Instances details
Eq ClosedOp Source # 
Instance details

Defined in RON.Types

Data ClosedOp Source # 
Instance details

Defined in RON.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClosedOp -> c ClosedOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClosedOp #

toConstr :: ClosedOp -> Constr #

dataTypeOf :: ClosedOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClosedOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClosedOp) #

gmapT :: (forall b. Data b => b -> b) -> ClosedOp -> ClosedOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClosedOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClosedOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> ClosedOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClosedOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClosedOp -> m ClosedOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClosedOp -> m ClosedOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClosedOp -> m ClosedOp #

Show ClosedOp Source # 
Instance details

Defined in RON.Types

Generic ClosedOp Source # 
Instance details

Defined in RON.Types

Associated Types

type Rep ClosedOp :: Type -> Type #

Methods

from :: ClosedOp -> Rep ClosedOp x #

to :: Rep ClosedOp x -> ClosedOp #

type Rep ClosedOp Source # 
Instance details

Defined in RON.Types

type Rep ClosedOp = D1 ('MetaData "ClosedOp" "RON.Types" "ron-0.12-H6CGha9E85SDsxBwhZfk7n" 'False) (C1 ('MetaCons "ClosedOp" 'PrefixI 'True) (S1 ('MetaSel ('Just "reducerId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UUID) :*: (S1 ('MetaSel ('Just "objectId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UUID) :*: S1 ('MetaSel ('Just "op") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Op))))

newtype ObjectRef a Source #

Reference to an object TODO hide data constructor in Internal module

Constructors

ObjectRef UUID 

Instances

Instances details
Eq (ObjectRef a) Source # 
Instance details

Defined in RON.Types

Methods

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

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

Typeable a => Show (ObjectRef a) Source # 
Instance details

Defined in RON.Types

Generic (ObjectRef a) Source # 
Instance details

Defined in RON.Types

Associated Types

type Rep (ObjectRef a) :: Type -> Type #

Methods

from :: ObjectRef a -> Rep (ObjectRef a) x #

to :: Rep (ObjectRef a) x -> ObjectRef a #

Hashable (ObjectRef a) Source # 
Instance details

Defined in RON.Types

Methods

hashWithSalt :: Int -> ObjectRef a -> Int #

hash :: ObjectRef a -> Int #

type Rep (ObjectRef a) Source # 
Instance details

Defined in RON.Types

type Rep (ObjectRef a) = D1 ('MetaData "ObjectRef" "RON.Types" "ron-0.12-H6CGha9E85SDsxBwhZfk7n" 'True) (C1 ('MetaCons "ObjectRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UUID)))

data ObjectFrame a Source #

Object reference accompanied with a frame

Constructors

ObjectFrame 

Fields

Instances

Instances details
Eq (ObjectFrame a) Source # 
Instance details

Defined in RON.Types

Show (ObjectFrame a) Source # 
Instance details

Defined in RON.Types

data Op Source #

Open op (operation)

Constructors

Op 

Fields

Instances

Instances details
Eq Op Source # 
Instance details

Defined in RON.Types

Methods

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

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

Data Op Source # 
Instance details

Defined in RON.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Op -> c Op #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Op #

toConstr :: Op -> Constr #

dataTypeOf :: Op -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Op) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Op) #

gmapT :: (forall b. Data b => b -> b) -> Op -> Op #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r #

gmapQ :: (forall d. Data d => d -> u) -> Op -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Op -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Op -> m Op #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op #

Show Op Source # 
Instance details

Defined in RON.Types

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

Generic Op Source # 
Instance details

Defined in RON.Types

Associated Types

type Rep Op :: Type -> Type #

Methods

from :: Op -> Rep Op x #

to :: Rep Op x -> Op #

Hashable Op Source # 
Instance details

Defined in RON.Types

Methods

hashWithSalt :: Int -> Op -> Int #

hash :: Op -> Int #

type Rep Op Source # 
Instance details

Defined in RON.Types

type OpenFrame = [Op] Source #

data OpTerm Source #

Op terminator

Constructors

TClosed 
TReduced 
THeader 
TQuery 

Instances

Instances details
Eq OpTerm Source # 
Instance details

Defined in RON.Types

Methods

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

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

Show OpTerm Source # 
Instance details

Defined in RON.Types

type Payload = [Atom] Source #

newtype StateChunk a Source #

Type-tagged version of WireStateChunk

Constructors

StateChunk [Op] 

type StateFrame = Map UUID WireStateChunk Source #

Frame containing only state chunks. Must contain one main object and any number of other objects that are part of the main one.

data UUID Source #

Universally unique identifier of anything

Constructors

UUID !Word64 !Word64 

Instances

Instances details
Eq UUID Source # 
Instance details

Defined in RON.UUID

Methods

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

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

Data UUID Source # 
Instance details

Defined in RON.UUID

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UUID -> c UUID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UUID #

toConstr :: UUID -> Constr #

dataTypeOf :: UUID -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UUID) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UUID) #

gmapT :: (forall b. Data b => b -> b) -> UUID -> UUID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r #

gmapQ :: (forall d. Data d => d -> u) -> UUID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UUID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

Ord UUID Source # 
Instance details

Defined in RON.UUID

Methods

compare :: UUID -> UUID -> Ordering #

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

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

(>) :: UUID -> UUID -> Bool #

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

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Show UUID Source #

RON-Text-encoding

Instance details

Defined in RON.UUID

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Generic UUID Source # 
Instance details

Defined in RON.UUID

Associated Types

type Rep UUID :: Type -> Type #

Methods

from :: UUID -> Rep UUID x #

to :: Rep UUID x -> UUID #

Hashable UUID Source # 
Instance details

Defined in RON.UUID

Methods

hashWithSalt :: Int -> UUID -> Int #

hash :: UUID -> Int #

type Rep UUID Source # 
Instance details

Defined in RON.UUID

type Rep UUID = D1 ('MetaData "UUID" "RON.UUID" "ron-0.12-H6CGha9E85SDsxBwhZfk7n" 'False) (C1 ('MetaCons "UUID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Word64)))

data WireChunk Source #

Common chunk

Instances

Instances details
Eq WireChunk Source # 
Instance details

Defined in RON.Types

Data WireChunk Source # 
Instance details

Defined in RON.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WireChunk -> c WireChunk #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WireChunk #

toConstr :: WireChunk -> Constr #

dataTypeOf :: WireChunk -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WireChunk) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WireChunk) #

gmapT :: (forall b. Data b => b -> b) -> WireChunk -> WireChunk #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WireChunk -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WireChunk -> r #

gmapQ :: (forall d. Data d => d -> u) -> WireChunk -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WireChunk -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WireChunk -> m WireChunk #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WireChunk -> m WireChunk #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WireChunk -> m WireChunk #

Show WireChunk Source # 
Instance details

Defined in RON.Types

Generic WireChunk Source # 
Instance details

Defined in RON.Types

Associated Types

type Rep WireChunk :: Type -> Type #

type Rep WireChunk Source # 
Instance details

Defined in RON.Types

type WireFrame = [WireChunk] Source #

Common frame

data WireReducedChunk Source #

Common reduced chunk

Constructors

WireReducedChunk 

Fields

Instances

Instances details
Eq WireReducedChunk Source # 
Instance details

Defined in RON.Types

Data WireReducedChunk Source # 
Instance details

Defined in RON.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WireReducedChunk -> c WireReducedChunk #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WireReducedChunk #

toConstr :: WireReducedChunk -> Constr #

dataTypeOf :: WireReducedChunk -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WireReducedChunk) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WireReducedChunk) #

gmapT :: (forall b. Data b => b -> b) -> WireReducedChunk -> WireReducedChunk #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WireReducedChunk -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WireReducedChunk -> r #

gmapQ :: (forall d. Data d => d -> u) -> WireReducedChunk -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WireReducedChunk -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WireReducedChunk -> m WireReducedChunk #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WireReducedChunk -> m WireReducedChunk #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WireReducedChunk -> m WireReducedChunk #

Show WireReducedChunk Source # 
Instance details

Defined in RON.Types

Generic WireReducedChunk Source # 
Instance details

Defined in RON.Types

Associated Types

type Rep WireReducedChunk :: Type -> Type #

type Rep WireReducedChunk Source # 
Instance details

Defined in RON.Types

type Rep WireReducedChunk = D1 ('MetaData "WireReducedChunk" "RON.Types" "ron-0.12-H6CGha9E85SDsxBwhZfk7n" 'False) (C1 ('MetaCons "WireReducedChunk" 'PrefixI 'True) (S1 ('MetaSel ('Just "wrcHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ClosedOp) :*: S1 ('MetaSel ('Just "wrcBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Op])))

data WireStateChunk Source #

Reduced chunk representing an object state (i. e. high-level value)

Constructors

WireStateChunk 

Fields

Instances

Instances details
Eq WireStateChunk Source # 
Instance details

Defined in RON.Types

Show WireStateChunk Source # 
Instance details

Defined in RON.Types

Op patterns

pattern AckP :: (Word2, Word2) Source #

pattern CreateP :: (Word2, Word2) Source #

pattern DeleteP :: (Word2, Word2) Source #

pattern RegularP :: (Word2, Word2) Source #

pattern UndeleteP :: (Word2, Word2) Source #