{-# LANGUAGE OverloadedLabels #-}
module Mensam.Server.Database.Space where
import Mensam.Server.Database.Schema
import Database.Selda qualified as Selda
spaceLookup ::
Selda.Text ->
Selda.Query backend (Selda.Row backend DbSpace)
spaceLookup :: forall backend. Text -> Query backend (Row backend DbSpace)
spaceLookup Text
name = do
Row backend DbSpace
dbSpace <- Table DbSpace -> Query backend (Row backend DbSpace)
forall a s. Relational a => Table a -> Query s (Row s a)
Selda.select Table DbSpace
tableSpace
Col backend Bool -> Query backend ()
forall s t. Same s t => Col s Bool -> Query t ()
Selda.restrict (Col backend Bool -> Query backend ())
-> Col backend Bool -> Query backend ()
forall a b. (a -> b) -> a -> b
$ Row backend DbSpace
dbSpace Row backend DbSpace -> Selector DbSpace Text -> Col backend Text
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbSpace Text
#dbSpace_name Col backend Text -> Col backend Text -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== Text -> Col backend Text
forall {k} a (s :: k). SqlType a => a -> Col s a
Selda.literal Text
name
Row backend DbSpace -> Query backend (Row backend DbSpace)
forall a. a -> Query backend a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Row backend DbSpace
dbSpace
spaceGet ::
Selda.ID DbSpace ->
Selda.Query backend (Selda.Row backend DbSpace)
spaceGet :: forall backend. ID DbSpace -> Query backend (Row backend DbSpace)
spaceGet ID DbSpace
identifier = do
Row backend DbSpace
dbSpace <- Table DbSpace -> Query backend (Row backend DbSpace)
forall a s. Relational a => Table a -> Query s (Row s a)
Selda.select Table DbSpace
tableSpace
Col backend Bool -> Query backend ()
forall s t. Same s t => Col s Bool -> Query t ()
Selda.restrict (Col backend Bool -> Query backend ())
-> Col backend Bool -> Query backend ()
forall a b. (a -> b) -> a -> b
$ Row backend DbSpace
dbSpace Row backend DbSpace
-> Selector DbSpace (ID DbSpace) -> Col backend (ID DbSpace)
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbSpace (ID DbSpace)
#dbSpace_id Col backend (ID DbSpace)
-> Col backend (ID DbSpace) -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== ID DbSpace -> Col backend (ID DbSpace)
forall {k} a (s :: k). SqlType a => a -> Col s a
Selda.literal ID DbSpace
identifier
Row backend DbSpace -> Query backend (Row backend DbSpace)
forall a. a -> Query backend a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Row backend DbSpace
dbSpace
spaceListRoles ::
Selda.ID DbSpace ->
Selda.Query backend (Selda.Row backend DbRole)
spaceListRoles :: forall backend. ID DbSpace -> Query backend (Row backend DbRole)
spaceListRoles ID DbSpace
space = do
Row backend DbRole
dbRole <- Table DbRole -> Query backend (Row backend DbRole)
forall a s. Relational a => Table a -> Query s (Row s a)
Selda.select Table DbRole
tableRole
Col backend Bool -> Query backend ()
forall s t. Same s t => Col s Bool -> Query t ()
Selda.restrict (Col backend Bool -> Query backend ())
-> Col backend Bool -> Query backend ()
forall a b. (a -> b) -> a -> b
$ Row backend DbRole
dbRole Row backend DbRole
-> Selector DbRole (ID DbSpace) -> Col backend (ID DbSpace)
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbRole (ID DbSpace)
#dbRole_space Col backend (ID DbSpace)
-> Col backend (ID DbSpace) -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== ID DbSpace -> Col backend (ID DbSpace)
forall {k} a (s :: k). SqlType a => a -> Col s a
Selda.literal ID DbSpace
space
Row backend DbRole -> Query backend (Row backend DbRole)
forall a. a -> Query backend a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Row backend DbRole
dbRole
spaceRoleLookup ::
Selda.ID DbSpace ->
Selda.Text ->
Selda.Query backend (Selda.Row backend DbRole)
spaceRoleLookup :: forall backend.
ID DbSpace -> Text -> Query backend (Row backend DbRole)
spaceRoleLookup ID DbSpace
space Text
name = do
Row backend DbRole
dbRole <- ID DbSpace -> Query backend (Row backend DbRole)
forall backend. ID DbSpace -> Query backend (Row backend DbRole)
spaceListRoles ID DbSpace
space
Col backend Bool -> Query backend ()
forall s t. Same s t => Col s Bool -> Query t ()
Selda.restrict (Col backend Bool -> Query backend ())
-> Col backend Bool -> Query backend ()
forall a b. (a -> b) -> a -> b
$ Row backend DbRole
dbRole Row backend DbRole -> Selector DbRole Text -> Col backend Text
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbRole Text
#dbRole_name Col backend Text -> Col backend Text -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== Text -> Col backend Text
forall {k} a (s :: k). SqlType a => a -> Col s a
Selda.literal Text
name
Row backend DbRole -> Query backend (Row backend DbRole)
forall a. a -> Query backend a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Row backend DbRole
dbRole
spaceRoleGet ::
Selda.ID DbRole ->
Selda.Query backend (Selda.Row backend DbRole)
spaceRoleGet :: forall backend. ID DbRole -> Query backend (Row backend DbRole)
spaceRoleGet ID DbRole
identifier = do
Row backend DbRole
dbRole <- Table DbRole -> Query backend (Row backend DbRole)
forall a s. Relational a => Table a -> Query s (Row s a)
Selda.select Table DbRole
tableRole
Col backend Bool -> Query backend ()
forall s t. Same s t => Col s Bool -> Query t ()
Selda.restrict (Col backend Bool -> Query backend ())
-> Col backend Bool -> Query backend ()
forall a b. (a -> b) -> a -> b
$ Row backend DbRole
dbRole Row backend DbRole
-> Selector DbRole (ID DbRole) -> Col backend (ID DbRole)
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbRole (ID DbRole)
#dbRole_id Col backend (ID DbRole)
-> Col backend (ID DbRole) -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== ID DbRole -> Col backend (ID DbRole)
forall {k} a (s :: k). SqlType a => a -> Col s a
Selda.literal ID DbRole
identifier
Row backend DbRole -> Query backend (Row backend DbRole)
forall a. a -> Query backend a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Row backend DbRole
dbRole
spaceRoleListPermissions ::
Selda.ID DbRole ->
Selda.Query backend (Selda.Row backend DbRolePermission)
spaceRoleListPermissions :: forall backend.
ID DbRole -> Query backend (Row backend DbRolePermission)
spaceRoleListPermissions ID DbRole
role = do
Row backend DbRolePermission
dbRolePermission <- Table DbRolePermission
-> Query backend (Row backend DbRolePermission)
forall a s. Relational a => Table a -> Query s (Row s a)
Selda.select Table DbRolePermission
tableRolePermission
Col backend Bool -> Query backend ()
forall s t. Same s t => Col s Bool -> Query t ()
Selda.restrict (Col backend Bool -> Query backend ())
-> Col backend Bool -> Query backend ()
forall a b. (a -> b) -> a -> b
$ Row backend DbRolePermission
dbRolePermission Row backend DbRolePermission
-> Selector DbRolePermission (ID DbRole) -> Col backend (ID DbRole)
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbRolePermission (ID DbRole)
#dbRolePermission_role Col backend (ID DbRole)
-> Col backend (ID DbRole) -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== ID DbRole -> Col backend (ID DbRole)
forall {k} a (s :: k). SqlType a => a -> Col s a
Selda.literal ID DbRole
role
Row backend DbRolePermission
-> Query backend (Row backend DbRolePermission)
forall a. a -> Query backend a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Row backend DbRolePermission
dbRolePermission
spaceUserGetRole ::
Selda.ID DbSpace ->
Selda.ID DbUser ->
Selda.Query backend (Selda.Col backend (Selda.ID DbRole))
spaceUserGetRole :: forall backend.
ID DbSpace -> ID DbUser -> Query backend (Col backend (ID DbRole))
spaceUserGetRole ID DbSpace
space ID DbUser
user = do
Row backend DbSpaceUser
dbSpaceUser <- Table DbSpaceUser -> Query backend (Row backend DbSpaceUser)
forall a s. Relational a => Table a -> Query s (Row s a)
Selda.select Table DbSpaceUser
tableSpaceUser
Col backend Bool -> Query backend ()
forall s t. Same s t => Col s Bool -> Query t ()
Selda.restrict (Col backend Bool -> Query backend ())
-> Col backend Bool -> Query backend ()
forall a b. (a -> b) -> a -> b
$
Row backend DbSpaceUser
dbSpaceUser Row backend DbSpaceUser
-> Selector DbSpaceUser (ID DbSpace) -> Col backend (ID DbSpace)
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbSpaceUser (ID DbSpace)
#dbSpaceUser_space Col backend (ID DbSpace)
-> Col backend (ID DbSpace) -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== ID DbSpace -> Col backend (ID DbSpace)
forall {k} a (s :: k). SqlType a => a -> Col s a
Selda.literal ID DbSpace
space
Col backend Bool -> Col backend Bool -> Col backend Bool
forall s t. Same s t => Col s Bool -> Col t Bool -> Col s Bool
Selda..&& Row backend DbSpaceUser
dbSpaceUser Row backend DbSpaceUser
-> Selector DbSpaceUser (ID DbUser) -> Col backend (ID DbUser)
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbSpaceUser (ID DbUser)
#dbSpaceUser_user Col backend (ID DbUser)
-> Col backend (ID DbUser) -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== ID DbUser -> Col backend (ID DbUser)
forall {k} a (s :: k). SqlType a => a -> Col s a
Selda.literal ID DbUser
user
Col backend (ID DbRole) -> Query backend (Col backend (ID DbRole))
forall a. a -> Query backend a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Col backend (ID DbRole)
-> Query backend (Col backend (ID DbRole)))
-> Col backend (ID DbRole)
-> Query backend (Col backend (ID DbRole))
forall a b. (a -> b) -> a -> b
$ Row backend DbSpaceUser
dbSpaceUser Row backend DbSpaceUser
-> Selector DbSpaceUser (ID DbRole) -> Col backend (ID DbRole)
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbSpaceUser (ID DbRole)
#dbSpaceUser_role
spaceUserListPermissions ::
Selda.ID DbSpace ->
Selda.ID DbUser ->
Selda.Query backend (Selda.Row backend DbRolePermission)
spaceUserListPermissions :: forall backend.
ID DbSpace
-> ID DbUser -> Query backend (Row backend DbRolePermission)
spaceUserListPermissions ID DbSpace
space ID DbUser
user = do
Col backend (ID DbRole)
dbRoleId <- ID DbSpace -> ID DbUser -> Query backend (Col backend (ID DbRole))
forall backend.
ID DbSpace -> ID DbUser -> Query backend (Col backend (ID DbRole))
spaceUserGetRole ID DbSpace
space ID DbUser
user
Row backend DbRolePermission
dbRolePermission <- Table DbRolePermission
-> Query backend (Row backend DbRolePermission)
forall a s. Relational a => Table a -> Query s (Row s a)
Selda.select Table DbRolePermission
tableRolePermission
Col backend Bool -> Query backend ()
forall s t. Same s t => Col s Bool -> Query t ()
Selda.restrict (Col backend Bool -> Query backend ())
-> Col backend Bool -> Query backend ()
forall a b. (a -> b) -> a -> b
$ Row backend DbRolePermission
dbRolePermission Row backend DbRolePermission
-> Selector DbRolePermission (ID DbRole) -> Col backend (ID DbRole)
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbRolePermission (ID DbRole)
#dbRolePermission_role Col backend (ID DbRole)
-> Col backend (ID DbRole) -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== Col backend (ID DbRole)
dbRoleId
Row backend DbRolePermission
-> Query backend (Row backend DbRolePermission)
forall a. a -> Query backend a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Row backend DbRolePermission
dbRolePermission
spaceListUsers ::
Selda.ID DbSpace ->
Selda.Query backend (Selda.Row backend DbSpaceUser)
spaceListUsers :: forall backend.
ID DbSpace -> Query backend (Row backend DbSpaceUser)
spaceListUsers ID DbSpace
space = do
Row backend DbSpaceUser
dbSpaceUser <- Table DbSpaceUser -> Query backend (Row backend DbSpaceUser)
forall a s. Relational a => Table a -> Query s (Row s a)
Selda.select Table DbSpaceUser
tableSpaceUser
Col backend Bool -> Query backend ()
forall s t. Same s t => Col s Bool -> Query t ()
Selda.restrict (Col backend Bool -> Query backend ())
-> Col backend Bool -> Query backend ()
forall a b. (a -> b) -> a -> b
$ Row backend DbSpaceUser
dbSpaceUser Row backend DbSpaceUser
-> Selector DbSpaceUser (ID DbSpace) -> Col backend (ID DbSpace)
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbSpaceUser (ID DbSpace)
#dbSpaceUser_space Col backend (ID DbSpace)
-> Col backend (ID DbSpace) -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== ID DbSpace -> Col backend (ID DbSpace)
forall {k} a (s :: k). SqlType a => a -> Col s a
Selda.literal ID DbSpace
space
Row backend DbSpaceUser -> Query backend (Row backend DbSpaceUser)
forall a. a -> Query backend a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Row backend DbSpaceUser
dbSpaceUser
spaceListDesks ::
Selda.ID DbSpace ->
Selda.Query backend (Selda.Row backend DbDesk)
spaceListDesks :: forall backend. ID DbSpace -> Query backend (Row backend DbDesk)
spaceListDesks ID DbSpace
space = do
Row backend DbDesk
dbDesk <- Table DbDesk -> Query backend (Row backend DbDesk)
forall a s. Relational a => Table a -> Query s (Row s a)
Selda.select Table DbDesk
tableDesk
Col backend Bool -> Query backend ()
forall s t. Same s t => Col s Bool -> Query t ()
Selda.restrict (Col backend Bool -> Query backend ())
-> Col backend Bool -> Query backend ()
forall a b. (a -> b) -> a -> b
$ Row backend DbDesk
dbDesk Row backend DbDesk
-> Selector DbDesk (ID DbSpace) -> Col backend (ID DbSpace)
forall a s t. SqlType a => Row s t -> Selector t a -> Col s a
Selda.! Selector DbDesk (ID DbSpace)
#dbDesk_space Col backend (ID DbSpace)
-> Col backend (ID DbSpace) -> Col backend Bool
forall s t a.
(Same s t, SqlType a) =>
Col s a -> Col t a -> Col s Bool
Selda..== ID DbSpace -> Col backend (ID DbSpace)
forall {k} a (s :: k). SqlType a => a -> Col s a
Selda.literal ID DbSpace
space
Row backend DbDesk -> Query backend (Row backend DbDesk)
forall a. a -> Query backend a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Row backend DbDesk
dbDesk