| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
DomainDriven.Persistance.Postgres.Internal
Description
Postgres events with state as an IORef
Synopsis
- data PostgresEvent model event = PostgresEvent {- connectionPool :: Pool Connection
- eventTableName :: EventTableName
- modelIORef :: IORef (NumberedModel model)
- app :: model -> Stored event -> model
- seed :: model
- chunkSize :: ChunkSize
 
- data PostgresEventTrans model event = PostgresEventTrans {- transaction :: OngoingTransaction
- eventTableName :: EventTableName
- modelIORef :: IORef (NumberedModel model)
- app :: model -> Stored event -> model
- seed :: model
- chunkSize :: ChunkSize
 
- getEventTableName :: EventTable -> EventTableName
- createEventTable :: (FromJSON e, WriteModel (PostgresEventTrans m e)) => PostgresEventTrans m e -> IO ()
- createEventTable' :: Connection -> EventTableName -> IO Int64
- retireTable :: Connection -> EventTableName -> IO ()
- createRetireFunction :: Connection -> IO ()
- simplePool' :: MonadUnliftIO m => ConnectInfo -> m (Pool Connection)
- simplePool :: MonadUnliftIO m => IO Connection -> m (Pool Connection)
- postgresWriteModelNoMigration :: (FromJSON e, WriteModel (PostgresEventTrans m e)) => Pool Connection -> EventTableName -> (m -> Stored e -> m) -> m -> IO (PostgresEvent m e)
- postgresWriteModel :: Pool Connection -> EventTable -> (m -> Stored e -> m) -> m -> IO (PostgresEvent m e)
- newtype Exists = Exists {}
- runMigrations :: OngoingTransaction -> EventTable -> IO ()
- createPostgresPersistance :: forall event model. Pool Connection -> EventTableName -> (model -> Stored event -> model) -> model -> IO (PostgresEvent model event)
- queryEvents :: FromJSON a => Connection -> EventTableName -> IO [(Stored a, EventNumber)]
- queryEventsAfter :: FromJSON a => Connection -> EventTableName -> EventNumber -> IO [(Stored a, EventNumber)]
- newtype EventQuery = EventQuery {- getPgQuery :: Query
 
- mkEventsAfterQuery :: EventTableName -> EventNumber -> EventQuery
- mkEventQuery :: EventTableName -> EventQuery
- headMay :: [a] -> Maybe a
- queryHasEventsAfter :: Connection -> EventTableName -> EventNumber -> IO Bool
- writeEvents :: forall a. ToJSON a => Connection -> EventTableName -> [Stored a] -> IO EventNumber
- getEventStream' :: FromJSON event => PostgresEventTrans model event -> SerialT IO (Stored event)
- withStreamReadTransaction :: forall t m a model event. (IsStream t, MonadAsync m, MonadCatch m) => PostgresEvent model event -> (PostgresEventTrans model event -> t m a) -> t m a
- withIOTrans :: forall a model event. PostgresEvent model event -> (PostgresEventTrans model event -> IO a) -> IO a
- mkEventStream :: FromJSON event => ChunkSize -> Connection -> EventQuery -> SerialT IO (Stored event, EventNumber)
- getModel' :: forall e m. FromJSON e => PostgresEventTrans m e -> IO m
- refreshModel :: forall m e. FromJSON e => PostgresEventTrans m e -> IO (m, EventNumber)
- exclusiveLock :: OngoingTransaction -> EventTableName -> IO ()
Documentation
data PostgresEvent model event Source #
Constructors
| PostgresEvent | |
| Fields 
 | |
Instances
data PostgresEventTrans model event Source #
Constructors
| PostgresEventTrans | |
| Fields 
 | |
Instances
createEventTable :: (FromJSON e, WriteModel (PostgresEventTrans m e)) => PostgresEventTrans m e -> IO () Source #
Create the table required for storing state and events, if they do not yet exist.
createEventTable' :: Connection -> EventTableName -> IO Int64 Source #
retireTable :: Connection -> EventTableName -> IO () Source #
createRetireFunction :: Connection -> IO () Source #
simplePool' :: MonadUnliftIO m => ConnectInfo -> m (Pool Connection) Source #
simplePool :: MonadUnliftIO m => IO Connection -> m (Pool Connection) Source #
postgresWriteModelNoMigration :: (FromJSON e, WriteModel (PostgresEventTrans m e)) => Pool Connection -> EventTableName -> (m -> Stored e -> m) -> m -> IO (PostgresEvent m e) Source #
Setup the persistance model and verify that the tables exist.
postgresWriteModel :: Pool Connection -> EventTable -> (m -> Stored e -> m) -> m -> IO (PostgresEvent m e) Source #
Setup the persistance model and verify that the tables exist.
runMigrations :: OngoingTransaction -> EventTable -> IO () Source #
createPostgresPersistance :: forall event model. Pool Connection -> EventTableName -> (model -> Stored event -> model) -> model -> IO (PostgresEvent model event) Source #
queryEvents :: FromJSON a => Connection -> EventTableName -> IO [(Stored a, EventNumber)] Source #
queryEventsAfter :: FromJSON a => Connection -> EventTableName -> EventNumber -> IO [(Stored a, EventNumber)] Source #
newtype EventQuery Source #
Constructors
| EventQuery | |
| Fields 
 | |
Instances
| Generic EventQuery Source # | |
| Defined in DomainDriven.Persistance.Postgres.Internal Associated Types type Rep EventQuery :: Type -> Type # | |
| Show EventQuery Source # | |
| Defined in DomainDriven.Persistance.Postgres.Internal Methods showsPrec :: Int -> EventQuery -> ShowS # show :: EventQuery -> String # showList :: [EventQuery] -> ShowS # | |
| type Rep EventQuery Source # | |
| Defined in DomainDriven.Persistance.Postgres.Internal type Rep EventQuery = D1 ('MetaData "EventQuery" "DomainDriven.Persistance.Postgres.Internal" "domaindriven-core-0.5.0-7rYqBJZZqKF59TNQHBa9rT" 'True) (C1 ('MetaCons "EventQuery" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPgQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Query))) | |
queryHasEventsAfter :: Connection -> EventTableName -> EventNumber -> IO Bool Source #
writeEvents :: forall a. ToJSON a => Connection -> EventTableName -> [Stored a] -> IO EventNumber Source #
getEventStream' :: FromJSON event => PostgresEventTrans model event -> SerialT IO (Stored event) Source #
withStreamReadTransaction :: forall t m a model event. (IsStream t, MonadAsync m, MonadCatch m) => PostgresEvent model event -> (PostgresEventTrans model event -> t m a) -> t m a Source #
A transaction that is always rolled back at the end. This is useful when using cursors as they can only be used inside a transaction.
withIOTrans :: forall a model event. PostgresEvent model event -> (PostgresEventTrans model event -> IO a) -> IO a Source #
mkEventStream :: FromJSON event => ChunkSize -> Connection -> EventQuery -> SerialT IO (Stored event, EventNumber) Source #
refreshModel :: forall m e. FromJSON e => PostgresEventTrans m e -> IO (m, EventNumber) Source #
exclusiveLock :: OngoingTransaction -> EventTableName -> IO () Source #