Skip to content

Commit

Permalink
Use JSONB aggregates to query contacts
Browse files Browse the repository at this point in the history
This converts a n+1 query into a single query
  • Loading branch information
jvanbruegge committed Feb 18, 2022
1 parent d93c3bc commit 75f90a2
Show file tree
Hide file tree
Showing 2 changed files with 19 additions and 14 deletions.
6 changes: 5 additions & 1 deletion backend/src/Data/ClientRequest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,8 @@ import Data.Text (Text)
import Data.Time.Calendar (Day)
import Data.User (Email, User (..))
import Data.Workmode (Workmode (..))
import Database.PostgreSQL.Simple.FromRow (FromRow (..), field)
import Database.PostgreSQL.Simple.FromField (fromJSONField)
import Database.PostgreSQL.Simple.FromRow (FromRow (..), field, fieldWith)
import Database.PostgreSQL.Simple.ToField (ToField (toField))
import Database.PostgreSQL.Simple.ToRow (ToRow (..))
import Database.PostgreSQL.Simple.Types (Null (Null))
Expand Down Expand Up @@ -65,6 +66,9 @@ data Office = MkOffice

data UserRegistration = MkUserRegistration Email Registration

instance FromRow Contacts where
fromRow = MkContacts <$> field <*> field <*> fieldWith fromJSONField

instance ToRow UserRegistration where
toRow (MkUserRegistration email MkRegistration {office, date, workmode}) =
[toField email, toField office, toField date] <> case workmode of
Expand Down
27 changes: 14 additions & 13 deletions backend/src/Database.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE TupleSections #-}

module Database where

Expand Down Expand Up @@ -46,18 +45,20 @@ queryBooked office start end =
queryContacts :: (MonadIO m, MonadReader Env m) => Email -> Day -> Day -> m [Contacts]
queryContacts email start end =
query'
"SELECT office, date FROM registrations WHERE workmode = 'Office' AND user_email = ? AND date >= ? AND date <= ? ORDER BY date DESC"
(email, start, end)
>>= mapM
( \t@(office, date) ->
MkContacts date office
<$> query'
( userFields <> " WHERE u.user_email IN ("
<> "SELECT r.user_email FROM registrations AS r WHERE workmode = 'Office' AND office = ? AND date = ?"
<> ")"
)
t
)
( "WITH dates AS ("
<> "SELECT date,office FROM registrations WHERE "
<> "workmode = 'Office' AND user_email = ? AND date >= ? AND date <= ?),"
<> "contacts AS ("
<> "SELECT date,office,user_email FROM registrations JOIN dates USING (date,office) "
<> "WHERE user_email <> ?),"
<> "user_fields AS (SELECT uf.name, uf.user_email AS email, uf.picture AS portrait, uf.default_office AS \"defaultOffice\", uf.is_admin AS \"isAdmin\" FROM ("
<> userFields
<> ") AS uf) "
<> "SELECT date,office,jsonb_agg(to_jsonb(user_fields.*)) AS contacts "
<> "FROM contacts JOIN user_fields ON contacts.user_email = user_fields.email "
<> "GROUP BY date, office ORDER BY date DESC"
)
(email, start, end, email)

tryRegistrations :: (MonadIO m, MonadReader Env m) => Maybe AdminUser -> Email -> [Registration] -> m (Maybe [Day])
tryRegistrations admin user xs = do
Expand Down

0 comments on commit 75f90a2

Please sign in to comment.