Skip to content

Commit

Permalink
Notify
Browse files Browse the repository at this point in the history
  • Loading branch information
echatav committed Jun 8, 2020
1 parent b23c44c commit 1ea0d07
Show file tree
Hide file tree
Showing 4 changed files with 85 additions and 0 deletions.
2 changes: 2 additions & 0 deletions squeal-postgresql/squeal-postgresql.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -74,6 +74,7 @@ library
Squeal.PostgreSQL.Session.Indexed
Squeal.PostgreSQL.Session.Migration
Squeal.PostgreSQL.Session.Monad
Squeal.PostgreSQL.Session.Notify
Squeal.PostgreSQL.Session.Oid
Squeal.PostgreSQL.Session.Pool
Squeal.PostgreSQL.Session.Result
Expand Down Expand Up @@ -103,6 +104,7 @@ library
, network-ip >= 0.3.0.3
, postgresql-binary >= 0.12.2
, postgresql-libpq >= 0.9.4.2
, postgresql-libpq-notify >= 0.1.0.0
, profunctors >= 5.5.2
, records-sop >= 0.1.0.3
, resource-pool >= 0.2.3.2
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ data SquealException
-- ^ unexpected number of columns
| RowsException Text LibPQ.Row LibPQ.Row
-- ^ too few rows, expected at least and actual number of rows
| NotificationException IOError
deriving (Eq, Show)
instance Exception SquealException

Expand Down
81 changes: 81 additions & 0 deletions squeal-postgresql/src/Squeal/PostgreSQL/Session/Notify.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,81 @@
{-|
Module: Squeal.PostgreSQL.Session.Notify
Description: database notification
Copyright: (c) Eitan Chatav, 2019
Maintainer: [email protected]
Stability: experimental
Support for receiving asynchronous notifications
via PostgreSQL's Listen/Notify mechanism.
See https://www.postgresql.org/docs/current/sql-notify.html
for more information.
-}

{-# LANGUAGE
DataKinds
, PolyKinds
, RankNTypes
, TypeOperators
#-}

module Squeal.PostgreSQL.Session.Notify
( getNotification
, getNotificationWithConfig
) where

import Data.Function ((&))
import UnliftIO

import qualified Database.PostgreSQL.LibPQ as LibPQ
import qualified Database.PostgreSQL.LibPQ.Notify as LibPQ
import qualified Generics.SOP as SOP

import Squeal.PostgreSQL.Session.Exception
import Squeal.PostgreSQL.Session

{-|
Returns a single notification. If no notifications are
available, 'getNotificationWithConfig' blocks until one arrives.
Unlike 'getNotification', 'getNotificationWithConfig' takes in an
additional 'Config' parameter which provides custom 'interrupt' and
various event hooks for operational insight.
Using a custom 'interrupt' is necessary if one would like to call
'getNotificationWithConfig' on one thread and @NOTIFY@ on another
thread using the same connection.
To support this behavior one must cause 'interrupt' to return after the
call to @NOTIFY@ checks it's result from the server.
See the test file of this package for an example of how to use a custom
'interrupt'.
Note that PostgreSQL does not
deliver notifications while a connection is inside a transaction.
-}
getNotificationWithConfig
:: MonadUnliftIO io
=> LibPQ.Config
-> PQ db db io LibPQ.Notify
getNotificationWithConfig config = PQ $ \ (SOP.K conn) -> do
noteOrErr <- liftIO $ LibPQ.getNotificationWithConfig config (&) conn

This comment has been minimized.

Copy link
@jfischoff

jfischoff Jun 8, 2020

So this is not ideal because getNotificationWithConfig will block and I guess hold onto the connection. If the connection was wrapped in a MVar getNotificationWithConfig will only hold the connection as it setup to wait on the notification but give up the lock as it is waiting.

I think this will work it just is not the best use of connections.

This comment has been minimized.

Copy link
@echatav

echatav Jun 8, 2020

Author Contributor

Squeal doesn't hold the connection in an MVar like postgresql-simple. Is this a reason it ought to?

This comment has been minimized.

Copy link
@jfischoff

jfischoff Jun 8, 2020

Is this a reason it ought to?

Maybe?

I'm not sure it needs an MVar specifically. A more general version might if instead it was a reader of (Connection -> IO a) or similar with the characteristics that lock/pool resource is only held in the continuation but not elsewhere.

I think it is useful to distinguish between the container that holds the connection and the block of code that locks the connection. Not sure that makes sense.

This comment has been minimized.

Copy link
@jfischoff

jfischoff Jun 9, 2020

I've been thinking about this more.

There is a race condition with this code. I thought it just affects a very special situation but that is not true.

The only way to prevent the race condition is to only use the connection for waiting on the notification, what your code is doing.

So I don't think you should change anything, but I am going to simplify my api because it can't work accomplish what I wanted it to anyway.

This comment has been minimized.

Copy link
@echatav

echatav Jun 9, 2020

Author Contributor

@jfischoff
So, I'm a bit confused because the Squeal session Monad, PQ is just a reader with a Connection:

newtype PQ
  (db0 :: SchemasType)
  (db1 :: SchemasType)
  (m :: Type -> Type)
  (x :: Type) =
    PQ { unPQ :: K LibPQ.Connection db0 -> m (K x db1) }

K is the type level constant, so it's isomorphic to ReaderT Connection.

This comment has been minimized.

Copy link
@echatav

echatav Jun 9, 2020

Author Contributor

Also just noticed there's a 0.2.0 version now with different signatures.

This comment has been minimized.

Copy link
@jfischoff

jfischoff Jun 9, 2020

Yeah I think the new version makes more sense in general and for squeal

case noteOrErr of
Left err -> throwSqueal (NotificationException err)
Right note -> return (SOP.K note)
{-|
Returns a single notification. If no notifications are
available, 'getNotification' blocks until one arrives.
If 'getNotification' is called and afterwards on a different thread
@NOTIFY@ is called using the same connection, 'getNotification' can
block even if a notification is sent.
To support this behavior one must use 'getNotificationWithConfig' instead.
Note that PostgreSQL does not
deliver notifications while a connection is inside a transaction.
-}
getNotification
:: MonadUnliftIO io
=> PQ db db io LibPQ.Notify
getNotification = getNotificationWithConfig LibPQ.defaultConfig
1 change: 1 addition & 0 deletions stack.lts-15.6.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -2,3 +2,4 @@ resolver: lts-15.6
packages:
- free-categories-0.2.0.0
- with-utf8-1.0.0.0
- postgresql-libpq-notify-0.1.0.0

0 comments on commit 1ea0d07

Please sign in to comment.