{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Hercules.API
( api,
servantApi,
servantClientApi,
swagger,
useApi,
enterApiE,
API,
ClientAuth,
HerculesAPI (..),
ClientAPI (..),
HerculesServantAPI,
AddAPIVersion,
Id,
Name,
Result (..),
NoContent (..),
noContent,
)
where
import Control.Lens
import Control.Monad
import Data.Proxy (Proxy (..))
import Data.Swagger hiding (Header)
import Hercules.API.Accounts (AccountsAPI)
import Hercules.API.Agents (AgentsAPI)
import Hercules.API.Build as Client
( BuildAPI,
)
import Hercules.API.Effects (EffectsAPI)
import Hercules.API.Health (HealthAPI)
import Hercules.API.Organizations (OrganizationsAPI)
import Hercules.API.Orphans ()
import Hercules.API.Prelude
import Hercules.API.Projects (ProjectsAPI)
import Hercules.API.Repos (ReposAPI)
import Hercules.API.Result (Result (..))
import Hercules.API.Servant (useApi)
import Hercules.API.State (StateAPI)
import Servant.API
import Servant.Auth
import Servant.Auth.Swagger ()
import Servant.Swagger
import Servant.Swagger.UI.Core (SwaggerSchemaUI)
data HerculesAPI auth f = HerculesAPI
{ forall auth f.
HerculesAPI auth f -> f :- ToServantApi (AccountsAPI auth)
accounts :: f :- ToServantApi (AccountsAPI auth),
forall auth f.
HerculesAPI auth f -> f :- ToServantApi (ReposAPI auth)
repos :: f :- ToServantApi (ReposAPI auth),
forall auth f.
HerculesAPI auth f -> f :- ToServantApi (ProjectsAPI auth)
projects :: f :- ToServantApi (ProjectsAPI auth),
forall auth f.
HerculesAPI auth f -> f :- ToServantApi (AgentsAPI auth)
agents :: f :- ToServantApi (AgentsAPI auth),
forall auth f.
HerculesAPI auth f -> f :- ToServantApi (BuildAPI auth)
build :: f :- ToServantApi (Client.BuildAPI auth),
forall auth f.
HerculesAPI auth f -> f :- ToServantApi (EffectsAPI auth)
effects :: f :- ToServantApi (EffectsAPI auth),
forall auth f.
HerculesAPI auth f -> f :- ToServantApi (HealthAPI auth)
health :: f :- ToServantApi (HealthAPI auth),
forall auth f.
HerculesAPI auth f -> f :- ToServantApi (OrganizationsAPI auth)
organizations :: f :- ToServantApi (OrganizationsAPI auth),
forall auth f.
HerculesAPI auth f -> f :- ToServantApi (StateAPI auth)
state :: f :- ToServantApi (StateAPI auth)
}
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall auth f x. Rep (HerculesAPI auth f) x -> HerculesAPI auth f
forall auth f x. HerculesAPI auth f -> Rep (HerculesAPI auth f) x
$cto :: forall auth f x. Rep (HerculesAPI auth f) x -> HerculesAPI auth f
$cfrom :: forall auth f x. HerculesAPI auth f -> Rep (HerculesAPI auth f) x
Generic)
data ClientAPI auth f = ClientAPI
{ forall auth f.
ClientAPI auth f -> f :- ToServantApi (AccountsAPI auth)
clientAccounts :: f :- ToServantApi (AccountsAPI auth),
forall auth f.
ClientAPI auth f -> f :- ToServantApi (ReposAPI auth)
clientRepos :: f :- ToServantApi (ReposAPI auth),
forall auth f.
ClientAPI auth f -> f :- ToServantApi (ProjectsAPI auth)
clientProjects :: f :- ToServantApi (ProjectsAPI auth),
forall auth f.
ClientAPI auth f -> f :- ToServantApi (AgentsAPI auth)
clientAgents :: f :- ToServantApi (AgentsAPI auth),
forall auth f.
ClientAPI auth f -> f :- ToServantApi (BuildAPI auth)
clientBuild :: f :- ToServantApi (Client.BuildAPI auth),
forall auth f.
ClientAPI auth f -> f :- ToServantApi (EffectsAPI auth)
clientEffects :: f :- ToServantApi (EffectsAPI auth),
forall auth f.
ClientAPI auth f -> f :- ToServantApi (OrganizationsAPI auth)
clientOrganizations :: f :- ToServantApi (OrganizationsAPI auth),
forall auth f.
ClientAPI auth f -> f :- ToServantApi (StateAPI auth)
clientState :: f :- ToServantApi (StateAPI auth)
}
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall auth f x. Rep (ClientAPI auth f) x -> ClientAPI auth f
forall auth f x. ClientAPI auth f -> Rep (ClientAPI auth f) x
$cto :: forall auth f x. Rep (ClientAPI auth f) x -> ClientAPI auth f
$cfrom :: forall auth f x. ClientAPI auth f -> Rep (ClientAPI auth f) x
Generic)
type ClientAuth = Auth '[JWT, Cookie] ()
type HerculesServantAPI auth = AddAPIVersion (ToServantApi (HerculesAPI auth))
type ClientServantAPI auth = AddAPIVersion (ToServantApi (ClientAPI auth))
type AddAPIVersion api = "api" :> "v1" :> api
servantApi :: Proxy (HerculesServantAPI auth)
servantApi :: forall auth. Proxy (HerculesServantAPI auth)
servantApi = forall {k} (t :: k). Proxy t
Proxy
servantClientApi :: Proxy (ClientServantAPI auth)
servantClientApi :: forall auth. Proxy (ClientServantAPI auth)
servantClientApi = forall {k} (t :: k). Proxy t
Proxy
type API auth =
HerculesServantAPI auth
:<|> "api"
:> SwaggerSchemaUI "v1" "swagger.json"
api :: Proxy (API auth)
api :: forall auth. Proxy (API auth)
api = forall {k} (t :: k). Proxy t
Proxy
swagger :: Swagger
swagger :: Swagger
swagger =
forall {k} (api :: k). HasSwagger api => Proxy api -> Swagger
toSwagger (forall auth. Proxy (ClientServantAPI auth)
servantClientApi @(Auth '[JWT] ()))
forall a b. a -> (a -> b) -> b
& forall s a. HasInfo s a => Lens' s a
info
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a. HasTitle s a => Lens' s a
title
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
"Hercules CI API"
forall a b. a -> (a -> b) -> b
& forall s a. HasInfo s a => Lens' s a
info
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a. HasVersion s a => Lens' s a
version
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
"v1"
forall a b. a -> (a -> b) -> b
& forall s a. HasInfo s a => Lens' s a
info
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a. HasDescription s a => Lens' s a
description
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"You have reached the Hercules Continuous Integration Application Programming Interface. This user interface provides human friendly access to the various endpoints. To get started with Hercules CI, see hercules-ci.com. Happy building! —the Hercules team"
noContent :: Functor m => m Servant.API.NoContent -> m ()
noContent :: forall (m :: * -> *). Functor m => m NoContent -> m ()
noContent = forall (f :: * -> *) a. Functor f => f a -> f ()
void