Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data GroupSite tag route = GroupSite {
- gsGetGroups :: route :- Get '[SCIM] (ListResponse (StoredGroup tag))
- gsGetGroup :: route :- (Capture "id" (GroupId tag) :> Get '[SCIM] (StoredGroup tag))
- gsPostGroup :: route :- (ReqBody '[SCIM] Group :> PostCreated '[SCIM] (StoredGroup tag))
- gsPutGroup :: route :- (Capture "id" (GroupId tag) :> (ReqBody '[SCIM] Group :> Put '[SCIM] (StoredGroup tag)))
- gsPatchGroup :: route :- (Capture "id" (GroupId tag) :> (ReqBody '[SCIM] Value :> Patch '[SCIM] (StoredGroup tag)))
- gsDeleteGroup :: route :- (Capture "id" (GroupId tag) :> DeleteNoContent)
- 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 -> Value -> ScimHandler m (StoredGroup tag)
- deleteGroup :: AuthInfo tag -> GroupId tag -> ScimHandler m ()
- class GroupTypes tag where
- type GroupId tag
- type StoredGroup tag = WithMeta (WithId (GroupId tag) Group)
- data Group = Group {
- schemas :: [Schema]
- displayName :: Text
- members :: [Member]
- data Member = Member {}
- groupServer :: forall tag m. (Show (GroupId tag), GroupDB tag m) => Maybe (AuthData tag) -> GroupSite tag (AsServerT (ScimHandler m))
Documentation
data GroupSite tag route Source #
GroupSite | |
|
Instances
class (Monad m, GroupTypes tag, AuthDB tag m) => GroupDB tag m where Source #
getGroups :: AuthInfo tag -> ScimHandler m (ListResponse (StoredGroup tag)) Source #
Get all groups.
getGroup :: AuthInfo tag -> GroupId tag -> ScimHandler m (StoredGroup tag) Source #
Get a single group by ID.
Should throw notFound
if the group does not.
postGroup :: AuthInfo tag -> Group -> ScimHandler m (StoredGroup tag) Source #
Create a new group.
Should throw conflict
if uniqueness constraints are violated.
putGroup :: AuthInfo tag -> GroupId tag -> Group -> ScimHandler m (StoredGroup tag) Source #
Overwrite an existing group.
Should throw notFound
if the group does not exist, and conflict
if uniqueness
constraints are violated.
:: AuthInfo tag | |
-> GroupId tag | |
-> Value | PATCH payload |
-> ScimHandler m (StoredGroup tag) |
Modify an existing group.
Should throw notFound
if the group doesn't exist, and conflict
if uniqueness
constraints are violated.
FUTUREWORK: add types for PATCH (instead of Value
).
See https://tools.ietf.org/html/rfc7644#section-3.5.2
deleteGroup :: AuthInfo tag -> GroupId tag -> ScimHandler m () Source #
Delete a group.
Should throw notFound
if the group does not exist.
Instances
GroupDB Mock TestServer Source # | |
Defined in Web.Scim.Server.Mock getGroups :: AuthInfo Mock -> ScimHandler TestServer (ListResponse (StoredGroup Mock)) Source # getGroup :: AuthInfo Mock -> GroupId Mock -> ScimHandler TestServer (StoredGroup Mock) Source # postGroup :: AuthInfo Mock -> Group -> ScimHandler TestServer (StoredGroup Mock) Source # putGroup :: AuthInfo Mock -> GroupId Mock -> Group -> ScimHandler TestServer (StoredGroup Mock) Source # patchGroup :: AuthInfo Mock -> GroupId Mock -> Value -> ScimHandler TestServer (StoredGroup Mock) Source # deleteGroup :: AuthInfo Mock -> GroupId Mock -> ScimHandler TestServer () Source # |
class GroupTypes tag Source #
Configurable parts of Group
.
Instances
GroupTypes Mock Source # | |
Defined in Web.Scim.Server.Mock | |
GroupTypes (TestTag id authData authInfo userExtra) Source # | |
Defined in Web.Scim.Test.Util |
Instances
Eq Member Source # | |
Show Member Source # | |
Generic Member Source # | |
ToJSON Member Source # | |
Defined in Web.Scim.Class.Group | |
FromJSON Member Source # | |
type Rep Member Source # | |
Defined in Web.Scim.Class.Group type Rep Member = D1 ('MetaData "Member" "Web.Scim.Class.Group" "hscim-0.3.6-JBBH5QJtoVCBhDdsGW2kZ7" 'False) (C1 ('MetaCons "Member" 'PrefixI 'True) (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "typ") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "ref") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) |