{-# LANGUAGE AllowAmbiguousTypes #-}
module Web.Scim.Class.Group
( GroupSite (..),
GroupDB (..),
GroupTypes (..),
StoredGroup,
Group (..),
Member (..),
groupServer,
)
where
import Data.Aeson
import qualified Data.Aeson as Aeson
import Data.Text
import Servant
import Servant.API.Generic
import Servant.Server.Generic
import Web.Scim.Class.Auth
import Web.Scim.ContentType
import Web.Scim.Handler
import Web.Scim.Schema.Common
import Web.Scim.Schema.ListResponse
import Web.Scim.Schema.Meta
type Schema = Text
class GroupTypes tag where
type GroupId tag
data Member = Member
{ Member -> Text
value :: Text,
Member -> Text
typ :: Text,
Member -> Text
ref :: Text
}
deriving (Int -> Member -> ShowS
[Member] -> ShowS
Member -> String
(Int -> Member -> ShowS)
-> (Member -> String) -> ([Member] -> ShowS) -> Show Member
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Member -> ShowS
showsPrec :: Int -> Member -> ShowS
$cshow :: Member -> String
show :: Member -> String
$cshowList :: [Member] -> ShowS
showList :: [Member] -> ShowS
Show, Member -> Member -> Bool
(Member -> Member -> Bool)
-> (Member -> Member -> Bool) -> Eq Member
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Member -> Member -> Bool
== :: Member -> Member -> Bool
$c/= :: Member -> Member -> Bool
/= :: Member -> Member -> Bool
Eq, (forall x. Member -> Rep Member x)
-> (forall x. Rep Member x -> Member) -> Generic Member
forall x. Rep Member x -> Member
forall x. Member -> Rep Member x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Member -> Rep Member x
from :: forall x. Member -> Rep Member x
$cto :: forall x. Rep Member x -> Member
to :: forall x. Rep Member x -> Member
Generic)
instance FromJSON Member where
parseJSON :: Value -> Parser Member
parseJSON = ([Text] -> Parser Member)
-> (Value -> Parser Member) -> Either [Text] Value -> Parser Member
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser Member
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Member)
-> ([Text] -> String) -> [Text] -> Parser Member
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> String
forall a. Show a => a -> String
show) (Options -> Value -> Parser Member
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
parseOptions) (Either [Text] Value -> Parser Member)
-> (Value -> Either [Text] Value) -> Value -> Parser Member
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Either [Text] Value
forall (m :: * -> *). (m ~ Either [Text]) => Value -> m Value
jsonLower
instance ToJSON Member where
toJSON :: Member -> Value
toJSON = Options -> Member -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
serializeOptions
data Group = Group
{ Group -> [Text]
schemas :: [Schema],
Group -> Text
displayName :: Text,
Group -> [Member]
members :: [Member]
}
deriving (Int -> Group -> ShowS
[Group] -> ShowS
Group -> String
(Int -> Group -> ShowS)
-> (Group -> String) -> ([Group] -> ShowS) -> Show Group
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Group -> ShowS
showsPrec :: Int -> Group -> ShowS
$cshow :: Group -> String
show :: Group -> String
$cshowList :: [Group] -> ShowS
showList :: [Group] -> ShowS
Show, Group -> Group -> Bool
(Group -> Group -> Bool) -> (Group -> Group -> Bool) -> Eq Group
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Group -> Group -> Bool
== :: Group -> Group -> Bool
$c/= :: Group -> Group -> Bool
/= :: Group -> Group -> Bool
Eq, (forall x. Group -> Rep Group x)
-> (forall x. Rep Group x -> Group) -> Generic Group
forall x. Rep Group x -> Group
forall x. Group -> Rep Group x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Group -> Rep Group x
from :: forall x. Group -> Rep Group x
$cto :: forall x. Rep Group x -> Group
to :: forall x. Rep Group x -> Group
Generic)
instance FromJSON Group where
parseJSON :: Value -> Parser Group
parseJSON = ([Text] -> Parser Group)
-> (Value -> Parser Group) -> Either [Text] Value -> Parser Group
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Parser Group
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Group)
-> ([Text] -> String) -> [Text] -> Parser Group
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> String
forall a. Show a => a -> String
show) (Options -> Value -> Parser Group
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
parseOptions) (Either [Text] Value -> Parser Group)
-> (Value -> Either [Text] Value) -> Value -> Parser Group
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Either [Text] Value
forall (m :: * -> *). (m ~ Either [Text]) => Value -> m Value
jsonLower
instance ToJSON Group where
toJSON :: Group -> Value
toJSON = Options -> Group -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
serializeOptions
type StoredGroup tag = WithMeta (WithId (GroupId tag) Group)
data GroupSite tag route = GroupSite
{ forall tag route.
GroupSite tag route
-> route :- Get '[SCIM] (ListResponse (StoredGroup tag))
gsGetGroups ::
route
:- Get '[SCIM] (ListResponse (StoredGroup tag)),
forall tag route.
GroupSite tag route
-> route
:- (Capture "id" (GroupId tag) :> Get '[SCIM] (StoredGroup tag))
gsGetGroup ::
route
:- Capture "id" (GroupId tag)
:> Get '[SCIM] (StoredGroup tag),
forall tag route.
GroupSite tag route
-> route
:- (ReqBody '[SCIM] Group :> PostCreated '[SCIM] (StoredGroup tag))
gsPostGroup ::
route
:- ReqBody '[SCIM] Group
:> PostCreated '[SCIM] (StoredGroup tag),
forall tag route.
GroupSite tag route
-> route
:- (Capture "id" (GroupId tag)
:> (ReqBody '[SCIM] Group :> Put '[SCIM] (StoredGroup tag)))
gsPutGroup ::
route
:- Capture "id" (GroupId tag)
:> ReqBody '[SCIM] Group
:> Put '[SCIM] (StoredGroup tag),
forall tag route.
GroupSite tag route
-> route
:- (Capture "id" (GroupId tag)
:> (ReqBody '[SCIM] Value :> Patch '[SCIM] (StoredGroup tag)))
gsPatchGroup ::
route
:- Capture "id" (GroupId tag)
:> ReqBody '[SCIM] Aeson.Value
:> Patch '[SCIM] (StoredGroup tag),
forall tag route.
GroupSite tag route
-> route :- (Capture "id" (GroupId tag) :> DeleteNoContent)
gsDeleteGroup ::
route
:- Capture "id" (GroupId tag)
:> DeleteNoContent
}
deriving ((forall x. GroupSite tag route -> Rep (GroupSite tag route) x)
-> (forall x. Rep (GroupSite tag route) x -> GroupSite tag route)
-> Generic (GroupSite tag route)
forall x. Rep (GroupSite tag route) x -> GroupSite tag route
forall x. GroupSite tag route -> Rep (GroupSite tag route) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall tag route x.
Rep (GroupSite tag route) x -> GroupSite tag route
forall tag route x.
GroupSite tag route -> Rep (GroupSite tag route) x
$cfrom :: forall tag route x.
GroupSite tag route -> Rep (GroupSite tag route) x
from :: forall x. GroupSite tag route -> Rep (GroupSite tag route) x
$cto :: forall tag route x.
Rep (GroupSite tag route) x -> GroupSite tag route
to :: forall x. Rep (GroupSite tag route) x -> GroupSite tag route
Generic)
class (Monad m, GroupTypes tag, AuthDB tag m) => GroupDB tag m where
getGroups ::
AuthInfo tag ->
ScimHandler m (ListResponse (StoredGroup tag))
getGroup ::
AuthInfo tag ->
GroupId tag ->
ScimHandler m (StoredGroup tag)
postGroup ::
AuthInfo tag ->
Group ->
ScimHandler m (StoredGroup tag)
putGroup ::
AuthInfo tag ->
GroupId tag ->
Group ->
ScimHandler m (StoredGroup tag)
patchGroup ::
AuthInfo tag ->
GroupId tag ->
Aeson.Value ->
ScimHandler m (StoredGroup tag)
deleteGroup ::
AuthInfo tag ->
GroupId tag ->
ScimHandler m ()
groupServer ::
forall tag m.
(GroupDB tag m) =>
Maybe (AuthData tag) ->
GroupSite tag (AsServerT (ScimHandler m))
groupServer :: forall tag (m :: * -> *).
GroupDB tag m =>
Maybe (AuthData tag) -> GroupSite tag (AsServerT (ScimHandler m))
groupServer Maybe (AuthData tag)
authData =
GroupSite
{ gsGetGroups :: AsServerT (ExceptT ScimError m)
:- Get '[SCIM] (ListResponse (StoredGroup tag))
gsGetGroups = do
AuthInfo tag
auth <- forall tag (m :: * -> *).
AuthDB tag m =>
Maybe (AuthData tag) -> ScimHandler m (AuthInfo tag)
authCheck @tag Maybe (AuthData tag)
authData
forall tag (m :: * -> *).
GroupDB tag m =>
AuthInfo tag -> ScimHandler m (ListResponse (StoredGroup tag))
getGroups @tag AuthInfo tag
auth,
gsGetGroup :: AsServerT (ExceptT ScimError m)
:- (Capture "id" (GroupId tag) :> Get '[SCIM] (StoredGroup tag))
gsGetGroup = \GroupId tag
gid -> do
AuthInfo tag
auth <- forall tag (m :: * -> *).
AuthDB tag m =>
Maybe (AuthData tag) -> ScimHandler m (AuthInfo tag)
authCheck @tag Maybe (AuthData tag)
authData
forall tag (m :: * -> *).
GroupDB tag m =>
AuthInfo tag -> GroupId tag -> ScimHandler m (StoredGroup tag)
getGroup @tag AuthInfo tag
auth GroupId tag
gid,
gsPostGroup :: AsServerT (ExceptT ScimError m)
:- (ReqBody '[SCIM] Group :> PostCreated '[SCIM] (StoredGroup tag))
gsPostGroup = \Group
gr -> do
AuthInfo tag
auth <- forall tag (m :: * -> *).
AuthDB tag m =>
Maybe (AuthData tag) -> ScimHandler m (AuthInfo tag)
authCheck @tag Maybe (AuthData tag)
authData
forall tag (m :: * -> *).
GroupDB tag m =>
AuthInfo tag -> Group -> ScimHandler m (StoredGroup tag)
postGroup @tag AuthInfo tag
auth Group
gr,
gsPutGroup :: AsServerT (ExceptT ScimError m)
:- (Capture "id" (GroupId tag)
:> (ReqBody '[SCIM] Group :> Put '[SCIM] (StoredGroup tag)))
gsPutGroup = \GroupId tag
gid Group
gr -> do
AuthInfo tag
auth <- forall tag (m :: * -> *).
AuthDB tag m =>
Maybe (AuthData tag) -> ScimHandler m (AuthInfo tag)
authCheck @tag Maybe (AuthData tag)
authData
forall tag (m :: * -> *).
GroupDB tag m =>
AuthInfo tag
-> GroupId tag -> Group -> ScimHandler m (StoredGroup tag)
putGroup @tag AuthInfo tag
auth GroupId tag
gid Group
gr,
gsPatchGroup :: AsServerT (ExceptT ScimError m)
:- (Capture "id" (GroupId tag)
:> (ReqBody '[SCIM] Value :> Patch '[SCIM] (StoredGroup tag)))
gsPatchGroup = \GroupId tag
gid Value
patch -> do
AuthInfo tag
auth <- forall tag (m :: * -> *).
AuthDB tag m =>
Maybe (AuthData tag) -> ScimHandler m (AuthInfo tag)
authCheck @tag Maybe (AuthData tag)
authData
forall tag (m :: * -> *).
GroupDB tag m =>
AuthInfo tag
-> GroupId tag -> Value -> ScimHandler m (StoredGroup tag)
patchGroup @tag AuthInfo tag
auth GroupId tag
gid Value
patch,
gsDeleteGroup :: AsServerT (ExceptT ScimError m)
:- (Capture "id" (GroupId tag) :> DeleteNoContent)
gsDeleteGroup = \GroupId tag
gid -> do
AuthInfo tag
auth <- forall tag (m :: * -> *).
AuthDB tag m =>
Maybe (AuthData tag) -> ScimHandler m (AuthInfo tag)
authCheck @tag Maybe (AuthData tag)
authData
forall tag (m :: * -> *).
GroupDB tag m =>
AuthInfo tag -> GroupId tag -> ScimHandler m ()
deleteGroup @tag AuthInfo tag
auth GroupId tag
gid
NoContent -> ExceptT ScimError m NoContent
forall a. a -> ExceptT ScimError m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure NoContent
NoContent
}