ron-0.12: RON
Safe HaskellNone
LanguageHaskell2010

RON.Event

Synopsis

Documentation

data CalendarTime Source #

Calendar format. See https://github.com/gritzko/ron/issues/19. Year range is 2010—2350. Precision is 100 ns.

data Event Source #

Generic Lamport time event. Cannot be Ord because we can't compare different types of clocks. If you want comparable events, use specific EpochEvent.

Constructors

Event 

Fields

Instances

Instances details
Eq Event Source # 
Instance details

Defined in RON.Event

Methods

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

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

Show Event Source # 
Instance details

Defined in RON.Event

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in RON.Event

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

type Rep Event Source # 
Instance details

Defined in RON.Event

type Rep Event = D1 ('MetaData "Event" "RON.Event" "ron-0.12-H6CGha9E85SDsxBwhZfk7n" 'False) (C1 ('MetaCons "Event" 'PrefixI 'True) (S1 ('MetaSel ('Just "time") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Time) :*: S1 ('MetaSel ('Just "replica") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Replica)))

newtype Time Source #

Clock type is encoded in 2 higher bits of variety, value in uuidValue

Constructors

Time Word64 

Instances

Instances details
Eq Time Source # 
Instance details

Defined in RON.Event

Methods

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

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

Ord Time Source # 
Instance details

Defined in RON.Event

Methods

compare :: Time -> Time -> Ordering #

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

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

(>) :: Time -> Time -> Bool #

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

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

Show Time Source # 
Instance details

Defined in RON.Event

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

newtype TimeVariety Source #

Constructors

TimeVariety Word2 

Bundled Patterns

pattern Calendar :: TimeVariety 
pattern Logical :: TimeVariety 
pattern Epoch :: TimeVariety

RFC 4122 epoch, hundreds of nanoseconds since 1582. Year range is 1582—5235.

pattern Unknown :: TimeVariety 

Instances

Instances details
Show TimeVariety Source # 
Instance details

Defined in RON.Event

newtype OriginVariety Source #

Replica id assignment style

Constructors

OriginVariety Word2 

Bundled Patterns

pattern TrieForked :: OriginVariety 
pattern CryptoForked :: OriginVariety 
pattern RecordForked :: OriginVariety 
pattern ApplicationSpecific :: OriginVariety 

Instances

Instances details
Show OriginVariety Source # 
Instance details

Defined in RON.Event

Hashable OriginVariety Source # 
Instance details

Defined in RON.Event

class Monad m => ReplicaClock m where Source #

Methods

getPid :: m Replica Source #

Get current replica id

getEvents Source #

Arguments

:: Word60

number of needed timestamps

-> m [Event] 

Get sequential timestamps.

Laws:

  1. t <- getEvents n
    (t !! i) == head t + i
    
  2. t1 <- getEvent
    t2 <- getEvent
    t2 >= t1 + 1
    
  3. getEvents 0 == getEvents 1

advance :: Word60 -> m () Source #

Make local time not less than this

Instances

Instances details
ReplicaClock EpochClock Source # 
Instance details

Defined in RON.Epoch

Monad m => ReplicaClock (ReplicaSimT m) Source # 
Instance details

Defined in RON.Event.Simulation

ReplicaClock m => ReplicaClock (ExceptT e m) Source # 
Instance details

Defined in RON.Event

ReplicaClock m => ReplicaClock (ReaderT r m) Source # 
Instance details

Defined in RON.Event

ReplicaClock m => ReplicaClock (StateT s m) Source # 
Instance details

Defined in RON.Event

(Monoid s, ReplicaClock m) => ReplicaClock (WriterT s m) Source # 
Instance details

Defined in RON.Event

newtype Replica Source #

Replica identifier. Implementation: naming (62-61) and origin (60-0 bits) fields from UUID

Constructors

Replica Word64 

Instances

Instances details
Eq Replica Source # 
Instance details

Defined in RON.Event

Methods

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

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

Ord Replica Source # 
Instance details

Defined in RON.Event

Show Replica Source # 
Instance details

Defined in RON.Event

Hashable Replica Source # 
Instance details

Defined in RON.Event

Methods

hashWithSalt :: Int -> Replica -> Int #

hash :: Replica -> Int #

advanceToUuid :: ReplicaClock clock => UUID -> clock () Source #

advance variant for any UUID

getEvent :: (HasCallStack, ReplicaClock m) => m Event Source #

Get a single event

getEventUuid :: ReplicaClock m => m UUID Source #

Get a single event as UUID

getEventUuids :: ReplicaClock m => Word60 -> m [UUID] Source #

Get event sequence as UUIDs

mkCalendarDate Source #

Arguments

:: (Word16, Word16, Word8)

date as (year, month [1..12], day [1..])

-> Maybe CalendarTime 

Make a calendar timestamp from a date

mkCalendarDateTime Source #

Arguments

:: (Word16, Word16, Word8)

date as (year, month [1..12], day [1..])

-> (Word8, Word8, Word8)

day time as (hours, minutes, seconds)

-> Maybe CalendarTime 

Make a calendar timestamp from a date and a day time

mkCalendarDateTimeNano Source #

Arguments

:: (Word16, Word16, Word8)

date as (year, month [1..12], day [1..])

-> (Word8, Word8, Word8)

day time as (hours, minutes, seconds)

-> Word32

fraction of a second in hundreds of nanosecond

-> Maybe CalendarTime 

Make a calendar timestamp from a date, a day time, and a second fraction

mkReplica :: OriginVariety -> Word60 -> Replica Source #

Make a replica id from OriginVariety and arbitrary number