hercules-ci-api-0.8.0.0: Hercules CI API definition with Servant
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hercules.API.Auth

Synopsis

Documentation

type OAuthReturn stage view = "api" :> ("auth" :> ("forge" :> (Capture "forge" (Id Forge) :> ("return" :> (QueryParam' '[stage, Strict] "code" Text :> (QueryParam' '[Optional, Strict] "redirect" Text :> view)))))) Source #

data AuthAPI auth f Source #

Endpoints for authentication

Constructors

AuthAPI 

Fields

Instances

Instances details
Generic (AuthAPI auth f) Source # 
Instance details

Defined in Hercules.API.Auth

Associated Types

type Rep (AuthAPI auth f) :: Type -> Type #

Methods

from :: AuthAPI auth f -> Rep (AuthAPI auth f) x #

to :: Rep (AuthAPI auth f) x -> AuthAPI auth f #

type Rep (AuthAPI auth f) Source # 
Instance details

Defined in Hercules.API.Auth

type Rep (AuthAPI auth f) = D1 ('MetaData "AuthAPI" "Hercules.API.Auth" "hercules-ci-api-0.8.0.0-inplace" 'False) (C1 ('MetaCons "AuthAPI" 'PrefixI 'True) ((S1 ('MetaSel ('Just "initiateGitHubLogin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- ("api" :> ("auth" :> ("github" :> (QueryParam' '[Optional, Strict] "redirect" Text :> Get302 '[PlainText, JSON] ('[] :: [Type]))))))) :*: S1 ('MetaSel ('Just "signOut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- (Summary "Terminate the session and help clear the cookies." :> ("api" :> ("auth" :> ("sign-out" :> (auth :> Post '[JSON] (Headers '[Header "Set-Cookie" SetCookie, Header "Set-Cookie" SetCookie] NoContent))))))))) :*: (S1 ('MetaSel ('Just "start") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- (Summary "Initiate an OAuth login, redirecting the client to a URL at the OAuth provider." :> ("api" :> ("auth" :> (Capture "type" Text :> ("start" :> (Capture "forgeId" (Id Forge) :> (QueryParam' '[Optional, Strict] "redirect" Text :> (auth :> Get302 '[PlainText, JSON] ('[] :: [Type]))))))))))) :*: S1 ('MetaSel ('Just "return") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- OAuthReturn Required (auth :> Get302 '[PlainText, JSON] '[Header "Set-Cookie" SetCookie, Header "Set-Cookie" SetCookie]))))))

data AuthRoutes view f Source #

Constructors

AuthRoutes 

Instances

Instances details
Generic (AuthRoutes view f) Source # 
Instance details

Defined in Hercules.API.Auth

Associated Types

type Rep (AuthRoutes view f) :: Type -> Type #

Methods

from :: AuthRoutes view f -> Rep (AuthRoutes view f) x #

to :: Rep (AuthRoutes view f) x -> AuthRoutes view f #

type Rep (AuthRoutes view f) Source # 
Instance details

Defined in Hercules.API.Auth

type Rep (AuthRoutes view f) = D1 ('MetaData "AuthRoutes" "Hercules.API.Auth" "hercules-ci-api-0.8.0.0-inplace" 'False) (C1 ('MetaCons "AuthRoutes" 'PrefixI 'True) (S1 ('MetaSel ('Just "authRouteReturn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f :- OAuthReturn Optional view))))