Copyright | (C) 2016 Yorick Laupa |
---|---|
License | (see the file LICENSE) |
Maintainer | Yorick Laupa <yo.eight@gmail.com> |
Stability | provisional |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Data
- newtype JsonParsing a = JsonParsing (Value -> Parser a)
- dataAsBytes :: Data -> ByteString
- dataFromBytes :: ByteString -> Data
- dataFromJson :: ToJSON a => a -> Data
- dataAsJson :: FromJSON a => Data -> Either Text a
- dataAsParsing :: Data -> JsonParsing a -> Either Text a
- dataAsParse :: Data -> (Value -> Parser a) -> Either Text a
- newtype Properties = Properties (Map Text Text)
- property :: MonadPlus m => Text -> Properties -> m Text
- singleton :: Text -> Text -> Properties
- setProperty :: Text -> Text -> Properties -> Properties
- properties :: Properties -> [(Text, Text)]
- newtype EventId = EventId UUID
- freshEventId :: MonadBase IO m => m EventId
- newtype StreamName = StreamName Text
- newtype EventType = EventType Text
- setEventType :: EventType -> State Event ()
- setEventId :: EventId -> State Event ()
- setEventPayload :: Data -> State Event ()
- setEventMetadata :: Properties -> State Event ()
- data Event = Event {
- eventType :: !EventType
- eventId :: !EventId
- eventPayload :: !Data
- eventMetadata :: !(Maybe Properties)
- newtype EventNumber = EventNumber Int64
- data SavedEvent = SavedEvent {
- eventNumber :: !EventNumber
- savedEvent :: !Event
- linkEvent :: !(Maybe Event)
- savedEventAs :: DecodeEvent a => SavedEvent -> Either Text a
- data Slice' a = Slice' {
- sliceEvents :: ![SavedEvent]
- sliceEndOfStream :: !Bool
- sliceNext :: !a
- type Slice = Slice' EventNumber
- sliceNextEventNumber :: Slice -> EventNumber
- sliceEventsAs :: DecodeEvent a => Slice -> Either Text [a]
- class EncodeEvent a where
- encodeEvent :: a -> State Event ()
- class DecodeEvent a where
- decodeEvent :: Event -> Either Text a
- newtype DecodeEventException = DecodeEventException Text
- data ExpectedVersion
- data ReadStatus a
- isReadSuccess :: ReadStatus a -> Bool
- isReadFailure :: ReadStatus a -> Bool
- data ReadFailure
Documentation
Opaque data type used to store raw data.
newtype JsonParsing a Source #
Sometimes, having to implement a FromJSON
instance isn't flexible enough.
JsonParsing
allow to pass parameters when parsing from a JSON value while
remaining composable.
JsonParsing (Value -> Parser a) |
Instances
Monad JsonParsing Source # | |
Defined in EventSource.Types (>>=) :: JsonParsing a -> (a -> JsonParsing b) -> JsonParsing b # (>>) :: JsonParsing a -> JsonParsing b -> JsonParsing b # return :: a -> JsonParsing a # fail :: String -> JsonParsing a # | |
Functor JsonParsing Source # | |
Defined in EventSource.Types fmap :: (a -> b) -> JsonParsing a -> JsonParsing b # (<$) :: a -> JsonParsing b -> JsonParsing a # | |
Applicative JsonParsing Source # | |
Defined in EventSource.Types pure :: a -> JsonParsing a # (<*>) :: JsonParsing (a -> b) -> JsonParsing a -> JsonParsing b # liftA2 :: (a -> b -> c) -> JsonParsing a -> JsonParsing b -> JsonParsing c # (*>) :: JsonParsing a -> JsonParsing b -> JsonParsing b # (<*) :: JsonParsing a -> JsonParsing b -> JsonParsing a # |
dataAsBytes :: Data -> ByteString Source #
Returns Data
content as a ByteString
.
dataFromBytes :: ByteString -> Data Source #
Creates a Data
object from a raw ByteString
.
dataAsParsing :: Data -> JsonParsing a -> Either Text a Source #
Uses a JsonParsing
comuputation to extract a value.
dataAsParse :: Data -> (Value -> Parser a) -> Either Text a Source #
Like dataAsParsing
but doesn't require you to use JsonParsing
.
newtype Properties Source #
Used to store a set a properties. One example is to be used as Event
metadata.
Instances
Show Properties Source # | |
Defined in EventSource.Types showsPrec :: Int -> Properties -> ShowS # show :: Properties -> String # showList :: [Properties] -> ShowS # | |
Semigroup Properties Source # | |
Defined in EventSource.Types (<>) :: Properties -> Properties -> Properties # sconcat :: NonEmpty Properties -> Properties # stimes :: Integral b => b -> Properties -> Properties # | |
Monoid Properties Source # | |
Defined in EventSource.Types mempty :: Properties # mappend :: Properties -> Properties -> Properties # mconcat :: [Properties] -> Properties # | |
ToJSON Properties Source # | |
Defined in EventSource.Types toJSON :: Properties -> Value # toEncoding :: Properties -> Encoding # toJSONList :: [Properties] -> Value # toEncodingList :: [Properties] -> Encoding # | |
FromJSON Properties Source # | |
Defined in EventSource.Types parseJSON :: Value -> Parser Properties # parseJSONList :: Value -> Parser [Properties] # |
property :: MonadPlus m => Text -> Properties -> m Text Source #
Retrieves a value associated with the given key.
singleton :: Text -> Text -> Properties Source #
Builds a Properties
with a single pair of key-value.
setProperty :: Text -> Text -> Properties -> Properties Source #
Adds a pair of key-value into given Properties
.
properties :: Properties -> [(Text, Text)] Source #
Returns all associated key-value pairs as a list.
Used to identify an event.
newtype StreamName Source #
Represents a stream name.
Instances
Used to identity the type of an Event
.
setEventMetadata :: Properties -> State Event () Source #
Sets metadata for an Event
.
Encapsulates an event which is about to be saved.
Event | |
|
Instances
Show Event Source # | |
DecodeEvent Event Source # | |
Defined in EventSource.Types | |
EncodeEvent Event Source # | |
Defined in EventSource.Types |
newtype EventNumber Source #
Represents an event index in a stream.
Instances
data SavedEvent Source #
Represents an event that's saved into the event store.
SavedEvent | |
|
Instances
Show SavedEvent Source # | |
Defined in EventSource.Types showsPrec :: Int -> SavedEvent -> ShowS # show :: SavedEvent -> String # showList :: [SavedEvent] -> ShowS # |
savedEventAs :: DecodeEvent a => SavedEvent -> Either Text a Source #
Deserializes a SavedEvent
.
Represents batch of events read from a store.
Slice' | |
|
type Slice = Slice' EventNumber Source #
sliceEventsAs :: DecodeEvent a => Slice -> Either Text [a] Source #
Deserializes a Slice'
s events.
class EncodeEvent a where Source #
Encodes a data object into an Event
. encodeEvent
get passed an
EventId
in a case where a fresh id is needed.
encodeEvent :: a -> State Event () Source #
Instances
EncodeEvent Event Source # | |
Defined in EventSource.Types |
class DecodeEvent a where Source #
Decodes an Event
into a data object.
Instances
DecodeEvent Event Source # | |
Defined in EventSource.Types |
newtype DecodeEventException Source #
Instances
Show DecodeEventException Source # | |
Defined in EventSource.Types showsPrec :: Int -> DecodeEventException -> ShowS # show :: DecodeEventException -> String # showList :: [DecodeEventException] -> ShowS # | |
Exception DecodeEventException Source # | |
Defined in EventSource.Types |
data ExpectedVersion Source #
The purpose of ExpectedVersion
is to make sure a certain stream state is
at an expected point in order to carry out a write.
Instances
Eq ExpectedVersion Source # | |
Defined in EventSource.Types (==) :: ExpectedVersion -> ExpectedVersion -> Bool # (/=) :: ExpectedVersion -> ExpectedVersion -> Bool # | |
Show ExpectedVersion Source # | |
Defined in EventSource.Types showsPrec :: Int -> ExpectedVersion -> ShowS # show :: ExpectedVersion -> String # showList :: [ExpectedVersion] -> ShowS # |
data ReadStatus a Source #
Statuses you can get on every read attempt.
Instances
isReadSuccess :: ReadStatus a -> Bool Source #
Returns True
is ReadStatus
is a ReadSuccess
.
isReadFailure :: ReadStatus a -> Bool Source #
Returns False
is ReadStatus
is a ReadStatus
.
data ReadFailure Source #
Represents the different kind of failure you can get when reading.
Instances
Show ReadFailure Source # | |
Defined in EventSource.Types showsPrec :: Int -> ReadFailure -> ShowS # show :: ReadFailure -> String # showList :: [ReadFailure] -> ShowS # | |
Exception ReadFailure Source # | |
Defined in EventSource.Types |