Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- app :: forall tag m. App tag m (SiteAPI tag) => Configuration -> (forall a. ScimHandler m a -> Handler a) -> Application
- mkapp :: forall tag m api. App tag m api => Proxy api -> ServerT api (ScimHandler m) -> (forall a. ScimHandler m a -> Handler a) -> Application
- type App tag m api = (DB tag m, Show (GroupId tag), HasServer api '[])
- type SiteAPI tag = ToServantApi (Site tag)
- data Site tag route = Site {}
- siteServer :: forall tag m. (DB tag m, Show (GroupId tag)) => Configuration -> Site tag (AsServerT (ScimHandler m))
- type ConfigAPI = ToServantApi ConfigSite
- configServer :: Monad m => Configuration -> ConfigSite (AsServerT (ScimHandler m))
- type UserAPI tag = ToServantApi (UserSite tag)
- userServer :: forall tag m. (AuthDB tag m, UserDB tag m) => Maybe (AuthData tag) -> UserSite tag (AsServerT (ScimHandler m))
- type GroupAPI tag = ToServantApi (GroupSite tag)
- groupServer :: forall tag m. (Show (GroupId tag), GroupDB tag m) => Maybe (AuthData tag) -> GroupSite tag (AsServerT (ScimHandler m))
WAI application
app :: forall tag m. App tag m (SiteAPI tag) => Configuration -> (forall a. ScimHandler m a -> Handler a) -> Application Source #
mkapp :: forall tag m api. App tag m api => Proxy api -> ServerT api (ScimHandler m) -> (forall a. ScimHandler m a -> Handler a) -> Application Source #
API tree
type SiteAPI tag = ToServantApi (Site tag) Source #
Instances
Generic (Site tag route) Source # | |
type Rep (Site tag route) Source # | |
Defined in Web.Scim.Server type Rep (Site tag route) = D1 ('MetaData "Site" "Web.Scim.Server" "hscim-0.3.6-JBBH5QJtoVCBhDdsGW2kZ7" 'False) (C1 ('MetaCons "Site" 'PrefixI 'True) (S1 ('MetaSel ('Just "config") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (route :- ConfigAPI)) :*: (S1 ('MetaSel ('Just "users") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (route :- (Header "Authorization" (AuthData tag) :> ("Users" :> UserAPI tag)))) :*: S1 ('MetaSel ('Just "groups") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (route :- (Header "Authorization" (AuthData tag) :> ("Groups" :> GroupAPI tag))))))) |
siteServer :: forall tag m. (DB tag m, Show (GroupId tag)) => Configuration -> Site tag (AsServerT (ScimHandler m)) Source #
API subtrees, useful for tests
type ConfigAPI = ToServantApi ConfigSite Source #
configServer :: Monad m => Configuration -> ConfigSite (AsServerT (ScimHandler m)) Source #
type UserAPI tag = ToServantApi (UserSite tag) Source #
userServer :: forall tag m. (AuthDB tag m, UserDB tag m) => Maybe (AuthData tag) -> UserSite tag (AsServerT (ScimHandler m)) Source #
type GroupAPI tag = ToServantApi (GroupSite tag) Source #