Safe Haskell | None |
---|---|
Language | Haskell2010 |
RON model types
Synopsis
- data Atom
- data ClosedOp = ClosedOp {}
- newtype ObjectRef a = ObjectRef UUID
- data ObjectFrame a = ObjectFrame {
- uuid :: UUID
- frame :: StateFrame
- data Op = Op {}
- type OpenFrame = [Op]
- data OpTerm
- type Payload = [Atom]
- newtype StateChunk a = StateChunk [Op]
- type StateFrame = Map UUID WireStateChunk
- data UUID = UUID !Word64 !Word64
- data WireChunk
- type WireFrame = [WireChunk]
- data WireReducedChunk = WireReducedChunk {}
- data WireStateChunk = WireStateChunk {}
- data OpPattern
- opPattern :: Op -> Maybe OpPattern
- pattern AckP :: (Word2, Word2)
- pattern AnnotationDerivedP :: (Word2, Word2)
- pattern AnnotationP :: (Word2, Word2)
- pattern CreateP :: (Word2, Word2)
- pattern DeleteP :: (Word2, Word2)
- pattern RegularP :: (Word2, Word2)
- pattern UndeleteP :: (Word2, Word2)
Documentation
Atom — a payload element
Instances
Eq Atom Source # | |
Data Atom Source # | |
Defined in RON.Types 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 # 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 # | |
IsString Atom Source # | |
Defined in RON.Types fromString :: String -> Atom # | |
Generic Atom Source # | |
Hashable Atom Source # | |
type Rep Atom Source # | |
Defined in RON.Types type Rep Atom = D1 ('MetaData "Atom" "RON.Types" "ron-0.12-H6CGha9E85SDsxBwhZfk7n" 'False) ((C1 ('MetaCons "AFloat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "AInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int64))) :+: (C1 ('MetaCons "AString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "AUuid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UUID)))) |
Closed op
Instances
Eq ClosedOp Source # | |
Data ClosedOp Source # | |
Defined in RON.Types 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 # | |
Generic ClosedOp Source # | |
type Rep ClosedOp Source # | |
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)))) |
Reference to an object TODO hide data constructor in Internal module
data ObjectFrame a Source #
Object reference accompanied with a frame
ObjectFrame | |
|
Instances
Eq (ObjectFrame a) Source # | |
Defined in RON.Types (==) :: ObjectFrame a -> ObjectFrame a -> Bool # (/=) :: ObjectFrame a -> ObjectFrame a -> Bool # | |
Show (ObjectFrame a) Source # | |
Defined in RON.Types showsPrec :: Int -> ObjectFrame a -> ShowS # show :: ObjectFrame a -> String # showList :: [ObjectFrame a] -> ShowS # |
Open op (operation)
Instances
Eq Op Source # | |
Data Op Source # | |
Defined in RON.Types 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 # 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 # | |
Generic Op Source # | |
Hashable Op Source # | |
type Rep Op Source # | |
Defined in RON.Types type Rep Op = D1 ('MetaData "Op" "RON.Types" "ron-0.12-H6CGha9E85SDsxBwhZfk7n" 'False) (C1 ('MetaCons "Op" 'PrefixI 'True) (S1 ('MetaSel ('Just "opId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UUID) :*: (S1 ('MetaSel ('Just "refId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UUID) :*: S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Payload)))) |
Op terminator
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.
Universally unique identifier of anything
Instances
Eq UUID Source # | |
Data UUID Source # | |
Defined in RON.UUID 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 # 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 # | |
Show UUID Source # | RON-Text-encoding |
Generic UUID Source # | |
Hashable UUID Source # | |
type Rep UUID Source # | |
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))) |
Common chunk
Instances
Eq WireChunk Source # | |
Data WireChunk Source # | |
Defined in RON.Types 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 # | |
Generic WireChunk Source # | |
type Rep WireChunk Source # | |
Defined in RON.Types type Rep WireChunk = D1 ('MetaData "WireChunk" "RON.Types" "ron-0.12-H6CGha9E85SDsxBwhZfk7n" 'False) (C1 ('MetaCons "Closed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ClosedOp)) :+: (C1 ('MetaCons "Value" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 WireReducedChunk)) :+: C1 ('MetaCons "Query" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 WireReducedChunk)))) |
data WireReducedChunk Source #
Common reduced chunk
Instances
data WireStateChunk Source #
Reduced chunk representing an object state (i. e. high-level value)
Instances
Eq WireStateChunk Source # | |
Defined in RON.Types (==) :: WireStateChunk -> WireStateChunk -> Bool # (/=) :: WireStateChunk -> WireStateChunk -> Bool # | |
Show WireStateChunk Source # | |
Defined in RON.Types showsPrec :: Int -> WireStateChunk -> ShowS # show :: WireStateChunk -> String # showList :: [WireStateChunk] -> ShowS # |
Op patterns
pattern AnnotationDerivedP :: (Word2, Word2) Source #
pattern AnnotationP :: (Word2, Word2) Source #