hscim-0.3.6: hscim json schema and server implementation
Safe HaskellNone
LanguageHaskell2010

Web.Scim.Class.Group

Synopsis

Documentation

data GroupSite tag route Source #

Constructors

GroupSite 

Fields

Instances

Instances details
Generic (GroupSite tag route) Source # 
Instance details

Defined in Web.Scim.Class.Group

Associated Types

type Rep (GroupSite tag route) :: Type -> Type #

Methods

from :: GroupSite tag route -> Rep (GroupSite tag route) x #

to :: Rep (GroupSite tag route) x -> GroupSite tag route #

type Rep (GroupSite tag route) Source # 
Instance details

Defined in Web.Scim.Class.Group

type Rep (GroupSite tag route) = D1 ('MetaData "GroupSite" "Web.Scim.Class.Group" "hscim-0.3.6-JBBH5QJtoVCBhDdsGW2kZ7" 'False) (C1 ('MetaCons "GroupSite" 'PrefixI 'True) ((S1 ('MetaSel ('Just "gsGetGroups") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (route :- Get '[SCIM] (ListResponse (StoredGroup tag)))) :*: (S1 ('MetaSel ('Just "gsGetGroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (route :- (Capture "id" (GroupId tag) :> Get '[SCIM] (StoredGroup tag)))) :*: S1 ('MetaSel ('Just "gsPostGroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (route :- (ReqBody '[SCIM] Group :> PostCreated '[SCIM] (StoredGroup tag)))))) :*: (S1 ('MetaSel ('Just "gsPutGroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (route :- (Capture "id" (GroupId tag) :> (ReqBody '[SCIM] Group :> Put '[SCIM] (StoredGroup tag))))) :*: (S1 ('MetaSel ('Just "gsPatchGroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (route :- (Capture "id" (GroupId tag) :> (ReqBody '[SCIM] Value :> Patch '[SCIM] (StoredGroup tag))))) :*: S1 ('MetaSel ('Just "gsDeleteGroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (route :- (Capture "id" (GroupId tag) :> DeleteNoContent)))))))

class (Monad m, GroupTypes tag, AuthDB tag m) => GroupDB tag m where Source #

Methods

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.

patchGroup Source #

Arguments

:: 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.

class GroupTypes tag Source #

Configurable parts of Group.

Associated Types

type GroupId tag Source #

Group ID type.

Instances

Instances details
GroupTypes Mock Source # 
Instance details

Defined in Web.Scim.Server.Mock

Associated Types

type GroupId Mock Source #

GroupTypes (TestTag id authData authInfo userExtra) Source # 
Instance details

Defined in Web.Scim.Test.Util

Associated Types

type GroupId (TestTag id authData authInfo userExtra) Source #

data Group Source #

Constructors

Group 

Fields

Instances

Instances details
Eq Group Source # 
Instance details

Defined in Web.Scim.Class.Group

Methods

(==) :: Group -> Group -> Bool #

(/=) :: Group -> Group -> Bool #

Show Group Source # 
Instance details

Defined in Web.Scim.Class.Group

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

Generic Group Source # 
Instance details

Defined in Web.Scim.Class.Group

Associated Types

type Rep Group :: Type -> Type #

Methods

from :: Group -> Rep Group x #

to :: Rep Group x -> Group #

ToJSON Group Source # 
Instance details

Defined in Web.Scim.Class.Group

FromJSON Group Source # 
Instance details

Defined in Web.Scim.Class.Group

type Rep Group Source # 
Instance details

Defined in Web.Scim.Class.Group

type Rep Group

data Member Source #

Constructors

Member 

Fields

Instances

Instances details
Eq Member Source # 
Instance details

Defined in Web.Scim.Class.Group

Methods

(==) :: Member -> Member -> Bool #

(/=) :: Member -> Member -> Bool #

Show Member Source # 
Instance details

Defined in Web.Scim.Class.Group

Generic Member Source # 
Instance details

Defined in Web.Scim.Class.Group

Associated Types

type Rep Member :: Type -> Type #

Methods

from :: Member -> Rep Member x #

to :: Rep Member x -> Member #

ToJSON Member Source # 
Instance details

Defined in Web.Scim.Class.Group

FromJSON Member Source # 
Instance details

Defined in Web.Scim.Class.Group

type Rep Member Source # 
Instance details

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))))

groupServer :: forall tag m. (Show (GroupId tag), GroupDB tag m) => Maybe (AuthData tag) -> GroupSite tag (AsServerT (ScimHandler m)) Source #