Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data CalendarTime = CalendarTime {}
- data Event = Event {}
- newtype Time = Time Word64
- newtype TimeVariety where
- TimeVariety Word2
- pattern Calendar :: TimeVariety
- pattern Logical :: TimeVariety
- pattern Epoch :: TimeVariety
- pattern Unknown :: TimeVariety
- newtype OriginVariety where
- OriginVariety Word2
- pattern TrieForked :: OriginVariety
- pattern CryptoForked :: OriginVariety
- pattern RecordForked :: OriginVariety
- pattern ApplicationSpecific :: OriginVariety
- class Monad m => ReplicaClock m where
- newtype Replica = Replica Word64
- advanceToUuid :: ReplicaClock clock => UUID -> clock ()
- decodeCalendar :: Word60 -> CalendarTime
- decodeEvent :: UUID -> Event
- decodeReplica :: UUID -> Replica
- encodeCalendar :: CalendarTime -> Word60
- encodeEvent :: Event -> UUID
- getEvent :: (HasCallStack, ReplicaClock m) => m Event
- getEventUuid :: ReplicaClock m => m UUID
- getEventUuids :: ReplicaClock m => Word60 -> m [UUID]
- mkCalendarDate :: (Word16, Word16, Word8) -> Maybe CalendarTime
- mkCalendarDateTime :: (Word16, Word16, Word8) -> (Word8, Word8, Word8) -> Maybe CalendarTime
- mkCalendarDateTimeNano :: (Word16, Word16, Word8) -> (Word8, Word8, Word8) -> Word32 -> Maybe CalendarTime
- mkCalendarEvent :: CalendarTime -> Replica -> Event
- mkReplica :: OriginVariety -> Word60 -> Replica
- mkTime :: TimeVariety -> Word60 -> Time
- timeValue :: Time -> Word60
- timeVariety :: Time -> TimeVariety
Documentation
data CalendarTime Source #
Calendar format. See https://github.com/gritzko/ron/issues/19. Year range is 2010—2350. Precision is 100 ns.
Instances
Eq CalendarTime Source # | |
Defined in RON.Event (==) :: CalendarTime -> CalendarTime -> Bool # (/=) :: CalendarTime -> CalendarTime -> Bool # | |
Ord CalendarTime Source # | |
Defined in RON.Event compare :: CalendarTime -> CalendarTime -> Ordering # (<) :: CalendarTime -> CalendarTime -> Bool # (<=) :: CalendarTime -> CalendarTime -> Bool # (>) :: CalendarTime -> CalendarTime -> Bool # (>=) :: CalendarTime -> CalendarTime -> Bool # max :: CalendarTime -> CalendarTime -> CalendarTime # min :: CalendarTime -> CalendarTime -> CalendarTime # | |
Show CalendarTime Source # | |
Defined in RON.Event showsPrec :: Int -> CalendarTime -> ShowS # show :: CalendarTime -> String # showList :: [CalendarTime] -> ShowS # |
Generic Lamport time event.
Cannot be Ord
because we can't compare different types of clocks.
If you want comparable events, use specific EpochEvent
.
Instances
Eq Event Source # | |
Show Event Source # | |
Generic Event Source # | |
type Rep Event Source # | |
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))) |
Clock type is encoded in 2 higher bits of variety, value in uuidValue
newtype TimeVariety Source #
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
Show TimeVariety Source # | |
Defined in RON.Event showsPrec :: Int -> TimeVariety -> ShowS # show :: TimeVariety -> String # showList :: [TimeVariety] -> ShowS # |
newtype OriginVariety Source #
Replica id assignment style
pattern TrieForked :: OriginVariety | |
pattern CryptoForked :: OriginVariety | |
pattern RecordForked :: OriginVariety | |
pattern ApplicationSpecific :: OriginVariety |
Instances
Show OriginVariety Source # | |
Defined in RON.Event showsPrec :: Int -> OriginVariety -> ShowS # show :: OriginVariety -> String # showList :: [OriginVariety] -> ShowS # | |
Hashable OriginVariety Source # | |
Defined in RON.Event hashWithSalt :: Int -> OriginVariety -> Int # hash :: OriginVariety -> Int # |
class Monad m => ReplicaClock m where Source #
Get current replica id
Get sequential timestamps.
Laws:
advance :: Word60 -> m () Source #
Make local time not less than this
Instances
ReplicaClock EpochClock Source # | |
Monad m => ReplicaClock (ReplicaSimT m) Source # | |
Defined in RON.Event.Simulation | |
ReplicaClock m => ReplicaClock (ExceptT e m) Source # | |
ReplicaClock m => ReplicaClock (ReaderT r m) Source # | |
ReplicaClock m => ReplicaClock (StateT s m) Source # | |
(Monoid s, ReplicaClock m) => ReplicaClock (WriterT s m) Source # | |
Replica identifier. Implementation: naming (62-61) and origin (60-0 bits) fields from UUID
advanceToUuid :: ReplicaClock clock => UUID -> clock () Source #
advance
variant for any UUID
decodeCalendar :: Word60 -> CalendarTime Source #
decodeEvent :: UUID -> Event Source #
decodeReplica :: UUID -> Replica Source #
encodeCalendar :: CalendarTime -> Word60 Source #
encodeEvent :: Event -> UUID Source #
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
:: (Word16, Word16, Word8) | date as (year, month [1..12], day [1..]) |
-> Maybe CalendarTime |
Make a calendar timestamp from a date
:: (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 #
:: (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
mkCalendarEvent :: CalendarTime -> Replica -> Event Source #
mkReplica :: OriginVariety -> Word60 -> Replica Source #
Make a replica id from OriginVariety
and arbitrary number
timeVariety :: Time -> TimeVariety Source #