{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Hercules.API
  ( api,
    servantApi,
    servantClientApi,
    swagger,
    useApi,
    enterApiE,
    API,
    ClientAuth,
    HerculesAPI (..),
    ClientAPI (..),
    HerculesServantAPI,
    AddAPIVersion,
    Id,
    Name,
    Result (..),

    -- * Reexports
    NoContent (..),

    -- * Utilities
    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.API.Generic
import Servant.Auth
import Servant.Auth.Swagger ()
import Servant.Swagger
import Servant.Swagger.UI.Core (SwaggerSchemaUI)

-- TODO remove health so we get clientapi
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 x. HerculesAPI auth f -> Rep (HerculesAPI auth f) x)
-> (forall x. Rep (HerculesAPI auth f) x -> HerculesAPI auth f)
-> Generic (HerculesAPI auth f)
forall x. Rep (HerculesAPI auth f) x -> HerculesAPI auth f
forall x. HerculesAPI auth f -> Rep (HerculesAPI auth f) x
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 x. ClientAPI auth f -> Rep (ClientAPI auth f) x)
-> (forall x. Rep (ClientAPI auth f) x -> ClientAPI auth f)
-> Generic (ClientAPI auth f)
forall x. Rep (ClientAPI auth f) x -> ClientAPI auth f
forall x. ClientAPI auth f -> Rep (ClientAPI auth f) x
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 = Proxy (HerculesServantAPI auth)
forall {k} (t :: k). Proxy t
Proxy

servantClientApi :: Proxy (ClientServantAPI auth)
servantClientApi :: forall auth. Proxy (ClientServantAPI auth)
servantClientApi = Proxy (ClientServantAPI auth)
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 = Proxy (API auth)
forall {k} (t :: k). Proxy t
Proxy

swagger :: Swagger
swagger :: Swagger
swagger =
  Proxy
  (AddAPIVersion
     ((((((("accounts"
            :> ("me"
                :> (((Summary "Get the account."
                      :> (Auth '[JWT] () :> Get '[JSON] Account))
                     :<|> (Summary "Get the account settings."
                           :> ("settings"
                               :> (Auth '[JWT] () :> Get '[JSON] AccountSettings))))
                    :<|> ((Summary "Update the account settings."
                           :> ("settings"
                               :> (ReqBody '[JSON] AccountSettingsPatch
                                   :> (Auth '[JWT] () :> Patch '[JSON] AccountSettings))))
                          :<|> (Summary "Disable all projects in the account."
                                :> ("disable-all-projects"
                                    :> (Auth '[JWT] () :> Post '[JSON] Int)))))))
           :<|> ((Summary "Retrieve notification settings"
                  :> ("accounts"
                      :> ("me"
                          :> ("settings"
                              :> ("notifications"
                                  :> (Auth '[JWT] () :> Get '[JSON] NotificationSettings))))))
                 :<|> (Summary "Update notification settings"
                       :> ("accounts"
                           :> ("me"
                               :> ("settings"
                                   :> ("notifications"
                                       :> (ReqBody '[JSON] NotificationSettingsPatch
                                           :> (Auth '[JWT] ()
                                               :> Patch '[JSON] NotificationSettings)))))))))
          :<|> (("accounts"
                 :> (Capture' '[] "accountId" (Id Account)
                     :> (((Summary "Get the account."
                           :> (Auth '[JWT] () :> Get '[JSON] Account))
                          :<|> (Summary "Get the account settings."
                                :> ("settings"
                                    :> (Auth '[JWT] () :> Get '[JSON] AccountSettings))))
                         :<|> ((Summary "Update the account settings."
                                :> ("settings"
                                    :> (ReqBody '[JSON] AccountSettingsPatch
                                        :> (Auth '[JWT] () :> Patch '[JSON] AccountSettings))))
                               :<|> (Summary "Disable all projects in the account."
                                     :> ("disable-all-projects"
                                         :> (Auth '[JWT] () :> Post '[JSON] Int)))))))
                :<|> (("site"
                       :> (Capture' '[] "site" (Name SourceHostingSite)
                           :> ("account"
                               :> (Capture' '[] "account" (Name Account)
                                   :> (((Summary "Get the account."
                                         :> (Auth '[JWT] () :> Get '[JSON] Account))
                                        :<|> (Summary "Get the account settings."
                                              :> ("settings"
                                                  :> (Auth '[JWT] ()
                                                      :> Get '[JSON] AccountSettings))))
                                       :<|> ((Summary "Update the account settings."
                                              :> ("settings"
                                                  :> (ReqBody '[JSON] AccountSettingsPatch
                                                      :> (Auth '[JWT] ()
                                                          :> Patch '[JSON] AccountSettings))))
                                             :<|> (Summary "Disable all projects in the account."
                                                   :> ("disable-all-projects"
                                                       :> (Auth '[JWT] ()
                                                           :> Post '[JSON] Int)))))))))
                      :<|> (Summary
                              "Accounts that the authenticated user owns, admins or collaborates with."
                            :> ("accounts"
                                :> (QueryParam "site" (Name SourceHostingSite)
                                    :> (QueryParam "name" (Name Account)
                                        :> (Auth '[JWT] () :> Get '[JSON] [Account]))))))))
         :<|> (((Summary "Create a request to authorize the CLI."
                 :> ("auth"
                     :> ("cli"
                         :> ("authorization"
                             :> ("request"
                                 :> (ReqBody '[JSON] CLIAuthorizationRequestCreate
                                     :> Post '[JSON] CLIAuthorizationRequestCreateResponse))))))
                :<|> ((Summary "Check the request status"
                       :> ("auth"
                           :> ("cli"
                               :> ("authorization"
                                   :> ("request"
                                       :> ("status"
                                           :> (Capture "temporaryToken" Text
                                               :> Get '[JSON] CLIAuthorizationRequestStatus)))))))
                      :<|> (Summary "Retrieve the request"
                            :> ("auth"
                                :> ("cli"
                                    :> ("authorization"
                                        :> ("request"
                                            :> (Capture "browserToken" Text
                                                :> (Auth '[JWT] ()
                                                    :> Get '[JSON] CLIAuthorizationRequest)))))))))
               :<|> (((Summary "Retrieve the request"
                       :> ("auth"
                           :> ("cli"
                               :> ("authorization"
                                   :> ("request"
                                       :> (Capture "browserToken" Text
                                           :> ("confirm"
                                               :> (Auth '[JWT] () :> Post '[JSON] NoContent))))))))
                      :<|> (Summary
                              "List the CLI tokens associated with the current account."
                            :> ("auth"
                                :> ("cli"
                                    :> ("tokens"
                                        :> (Auth '[JWT] () :> Get '[JSON] CLITokensResponse))))))
                     :<|> ((Summary "Permanently disallow the use of a CLI token."
                            :> ("auth"
                                :> ("cli"
                                    :> ("tokens"
                                        :> (Capture "cliTokenId" (Id "CLIToken")
                                            :> ("revoke"
                                                :> (Auth '[JWT] () :> Post '[JSON] NoContent)))))))
                           :<|> (Summary
                                   "Retrieve installation status after redirect from external source site settings."
                                 :> ("sites"
                                     :> (Capture "siteId" (Id SourceHostingSite)
                                         :> ("installation"
                                             :> (Capture "installationId" Int
                                                 :> ("status"
                                                     :> (Auth '[JWT] ()
                                                         :> Get
                                                              '[JSON]
                                                              AccountInstallationStatus)))))))))))
        :<|> ((Summary
                 "Repositories that the account owns or has explicit access to."
               :> ("accounts"
                   :> (Capture' '[Required, Strict] "accountId" (Id Account)
                       :> ("repos" :> (Auth '[JWT] () :> Get '[JSON] [Repo])))))
              :<|> (Summary
                      "Parse a git remote URL into site, owner and repo. Returns 400 if invalid, 404 if the site can not be determined. Does provide any guarantee that the repository exists."
                    :> ("parse-git-url"
                        :> (QueryParam' '[Required, Strict] "gitURL" Text
                            :> (Auth '[JWT] () :> Get '[JSON] RepoKey))))))
       :<|> ((((("projects"
                 :> (Capture' '[Required, Strict] "projectId" (Id Project)
                     :> ((Summary "Retrieve information about jobs"
                          :> ("jobs"
                              :> (QueryParam'
                                    '[Optional,
                                      Description
                                        "Constrain the results by git ref, such as refs/heads/my-branch or HEAD"]
                                    "ref"
                                    Text
                                  :> (QueryParam'
                                        '[Optional,
                                          Description
                                            "Only return successful jobs, or only failed ones"]
                                        "success"
                                        Bool
                                      :> (QueryParam'
                                            '[Optional,
                                              Description
                                                "Return jobs that come \"after\" the provided id in the response order."]
                                            "offsetId"
                                            (Id Job)
                                          :> (Auth '[JWT] () :> Get '[JSON] PagedJobs))))))
                         :<|> (Summary
                                 "Get source information from the latest successful job/jobs satisfying the provided requirements."
                               :> (Description
                                     "The job parameter can be omitted to require all jobs for a commit to succeed. This can have the unexpected effect of reverting when a change in the extraInputs causes a regression. So it is recommended to specify one or more jobs. Common examples are \"onPush.default\" for a pinned build or \"onPush.ci\" for a build using extraInputs to integrate continuously."
                                   :> ("source"
                                       :> (QueryParam'
                                             '[Optional,
                                               Description
                                                 "Constrain the results by git ref, such as refs/heads/my-branch. Defaults to HEAD."]
                                             "ref"
                                             Text
                                           :> (QueryParams "jobs" Text
                                               :> (Auth '[JWT] ()
                                                   :> Get '[JSON] ImmutableGitInput)))))))))
                :<|> (("site"
                       :> (Capture' '[Required, Strict] "site" (Name SourceHostingSite)
                           :> ("account"
                               :> (Capture' '[Required, Strict] "account" (Name Account)
                                   :> ("project"
                                       :> (Capture' '[Required, Strict] "project" (Name Project)
                                           :> ((Summary "Retrieve information about jobs"
                                                :> ("jobs"
                                                    :> (QueryParam'
                                                          '[Optional,
                                                            Description
                                                              "Constrain the results by git ref, such as refs/heads/my-branch or HEAD"]
                                                          "ref"
                                                          Text
                                                        :> (QueryParam'
                                                              '[Optional,
                                                                Description
                                                                  "Only return successful jobs, or only failed ones"]
                                                              "success"
                                                              Bool
                                                            :> (QueryParam'
                                                                  '[Optional,
                                                                    Description
                                                                      "Return jobs that come \"after\" the provided id in the response order."]
                                                                  "offsetId"
                                                                  (Id Job)
                                                                :> (Auth '[JWT] ()
                                                                    :> Get '[JSON] PagedJobs))))))
                                               :<|> (Summary
                                                       "Get source information from the latest successful job/jobs satisfying the provided requirements."
                                                     :> (Description
                                                           "The job parameter can be omitted to require all jobs for a commit to succeed. This can have the unexpected effect of reverting when a change in the extraInputs causes a regression. So it is recommended to specify one or more jobs. Common examples are \"onPush.default\" for a pinned build or \"onPush.ci\" for a build using extraInputs to integrate continuously."
                                                         :> ("source"
                                                             :> (QueryParam'
                                                                   '[Optional,
                                                                     Description
                                                                       "Constrain the results by git ref, such as refs/heads/my-branch. Defaults to HEAD."]
                                                                   "ref"
                                                                   Text
                                                                 :> (QueryParams "jobs" Text
                                                                     :> (Auth '[JWT] ()
                                                                         :> Get
                                                                              '[JSON]
                                                                              ImmutableGitInput)))))))))))))
                      :<|> (Summary "List all projects owned by an account."
                            :> ("accounts"
                                :> (Capture' '[Required, Strict] "accountId" (Id Account)
                                    :> ("projects"
                                        :> (Auth '[JWT] () :> Get '[JSON] [Project])))))))
               :<|> ((Summary "Find projects"
                      :> ("projects"
                          :> (QueryParam' '[Optional] "site" (Name SourceHostingSite)
                              :> (QueryParam' '[Optional] "account" (Name Account)
                                  :> (QueryParam' '[Optional] "project" (Name Project)
                                      :> (Auth '[JWT] () :> Get '[JSON] [Project]))))))
                     :<|> ((Summary "Create a new project."
                            :> ("projects"
                                :> (Auth '[JWT] ()
                                    :> (ReqBody '[JSON] CreateProject
                                        :> Post '[JSON] (Id Project)))))
                           :<|> (Summary "Modify a project"
                                 :> ("projects"
                                     :> (Capture' '[Required, Strict] "projectId" (Id Project)
                                         :> (ReqBody '[JSON] PatchProject
                                             :> (Auth '[JWT] () :> Patch '[JSON] Project))))))))
              :<|> (((Summary "Create a token for local effect execution"
                      :> ("projects"
                          :> (Capture' '[Required, Strict] "projectId" (Id Project)
                              :> (Auth '[JWT] ()
                                  :> ("create-user-effect-token"
                                      :> Post '[JSON] CreateUserEffectTokenResponse)))))
                     :<|> ((Summary "Find jobs"
                            :> ("jobs"
                                :> (QueryParam'
                                      '[Optional,
                                        Description "Currently only \"github\" or omit entirely"]
                                      "site"
                                      (Name SourceHostingSite)
                                    :> (QueryParam'
                                          '[Optional, Description "Account name filter"]
                                          "account"
                                          (Name Account)
                                        :> (QueryParam'
                                              '[Optional,
                                                Description
                                                  "Project name filter. Required if you want to retrieve all jobs"]
                                              "project"
                                              (Name Project)
                                            :> (QueryParam'
                                                  '[Optional,
                                                    Description "To get a specific job by index"]
                                                  "index"
                                                  Int
                                                :> (QueryParam'
                                                      '[Optional,
                                                        Description
                                                          "Number of latest jobs to get, when project name is omitted. Range [1..50], default 10."]
                                                      "latest"
                                                      Int
                                                    :> (Auth '[JWT] ()
                                                        :> Get '[JSON] [ProjectAndJobs]))))))))
                           :<|> (Summary "List all attributes in a job"
                                 :> (Description
                                       "A list of all attributes that have been produced as part of the evaluation of a job."
                                     :> ("jobs"
                                         :> (Capture' '[Required, Strict] "jobId" (Id Job)
                                             :> ("evaluation"
                                                 :> (Auth '[JWT] ()
                                                     :> Get '[JSON] EvaluationDetail))))))))
                    :<|> (((Summary "Find all failures in an evaluation's derivations"
                            :> (Description
                                  "Returns all derivations that have failures in their dependency closures."
                                :> ("jobs"
                                    :> (Capture' '[Required, Strict] "jobId" (Id Job)
                                        :> ("derivations"
                                            :> ("failed"
                                                :> (Auth '[JWT] () :> Get '[JSON] Graph)))))))
                           :<|> (Summary "Create a new job like this job"
                                 :> (Description
                                       "The newly created job will be in the same project, have the same inputs but a new evaluation. The response has the newly created job."
                                     :> ("jobs"
                                         :> (Capture' '[Required, Strict] "jobId" (Id Job)
                                             :> ("rerun"
                                                 :> (QueryParam "rebuildFailures" Bool
                                                     :> (Auth '[JWT] () :> Post '[JSON] Job))))))))
                          :<|> ((Summary "Cancel the job and any work that becomes redundant"
                                 :> (Description
                                       "Some derivations may keep going, if referenced by active jobs."
                                     :> ("jobs"
                                         :> (Capture' '[Required, Strict] "jobId" (Id Job)
                                             :> ("cancel"
                                                 :> (Auth '[JWT] () :> Post '[JSON] NoContent))))))
                                :<|> (Summary "Read all recorded evaluation log entries"
                                      :> ("jobs"
                                          :> (Capture' '[Required, Strict] "jobId" (Id Job)
                                              :> ("evaluation"
                                                  :> ("log"
                                                      :> ("lines"
                                                          :> (QueryParam'
                                                                '[Required] "logId" (Id "log")
                                                              :> (QueryParam' '[Optional] "iMin" Int
                                                                  :> (Auth '[JWT] ()
                                                                      :> Get
                                                                           '[JSON] Log)))))))))))))
             :<|> (((Summary "List all cluster join tokens in an account."
                     :> ("accounts"
                         :> (Capture' '[Required, Strict] "accountId" (Id Account)
                             :> ("clusterJoinTokens"
                                 :> (Auth '[JWT] () :> Get '[JSON] [ClusterJoinToken])))))
                    :<|> (Summary
                            "Generate a new cluster join token for agents to be added to this account."
                          :> ("accounts"
                              :> (Capture' '[Required, Strict] "accountId" (Id Account)
                                  :> ("clusterJoinTokens"
                                      :> (ReqBody '[JSON] CreateClusterJoinToken
                                          :> (Auth '[JWT] ()
                                              :> Post '[JSON] FullClusterJoinToken)))))))
                   :<|> ((Summary
                            "Delete an cluster join token in the account. No new agents will be able to join this account with the specified token."
                          :> ("accounts"
                              :> (Capture' '[Required, Strict] "accountId" (Id Account)
                                  :> ("clusterJoinTokens"
                                      :> (Capture'
                                            '[Required, Strict]
                                            "clusterJoinTokenId"
                                            (Id ClusterJoinToken)
                                          :> (Auth '[JWT] () :> Delete '[JSON] NoContent))))))
                         :<|> (Summary "Show the agents sessions owned by the account."
                               :> ("accounts"
                                   :> (Capture' '[Required, Strict] "accountId" (Id Account)
                                       :> ("agentSessions"
                                           :> (Auth '[JWT] () :> Get '[JSON] [AgentSession])))))))))
      :<|> (((((Summary "Restart a derivation"
                :> ("accounts"
                    :> (Capture' '[] "accountId" (Id Account)
                        :> ("derivations"
                            :> (Capture "derivationPath" Text
                                :> ("retry"
                                    :> (Auth '[JWT] () :> Post '[PlainText, JSON] NoContent)))))))
               :<|> (Summary "Read a derivation build log"
                     :> (Description "This interface may change."
                         :> ("accounts"
                             :> (Capture' '[] "accountId" (Id Account)
                                 :> ("derivations"
                                     :> (Capture "derivationPath" Text
                                         :> ("log"
                                             :> (QueryParam "logId" (Id "log")
                                                 :> (Auth '[JWT] ()
                                                     :> Get '[PlainText, JSON] Text))))))))))
              :<|> ((Summary "Read all recorded log entries"
                     :> ("accounts"
                         :> (Capture' '[] "accountId" (Id Account)
                             :> ("derivations"
                                 :> (Capture "derivationPath" Text
                                     :> ("log"
                                         :> ("lines"
                                             :> (QueryParam' '[Required] "logId" (Id "log")
                                                 :> (QueryParam' '[Optional] "iMin" Int
                                                     :> (Auth '[JWT] () :> Get '[JSON] Log))))))))))
                    :<|> (Summary "Get information about a derivation."
                          :> (Description
                                "Optionally, a job id can be specified to provide context."
                              :> ("accounts"
                                  :> (Capture' '[] "accountId" (Id Account)
                                      :> ("derivations"
                                          :> (Capture "derivationPath" Text
                                              :> (QueryParam' '[Optional, Strict] "via-job" (Id Job)
                                                  :> (Auth '[JWT] ()
                                                      :> Get '[JSON] DerivationInfo))))))))))
             :<|> ((Summary "Read effect events"
                    :> ("jobs"
                        :> (Capture "jobId" (Id Job)
                            :> ("effects"
                                :> (Capture "attribute" AttributePath
                                    :> (Auth '[JWT] () :> Get '[JSON] EffectInfo))))))
                   :<|> ((Summary "Read all recorded log entries"
                          :> ("jobs"
                              :> (Capture "jobId" (Id Job)
                                  :> ("effects"
                                      :> (Capture "attribute" AttributePath
                                          :> ("log"
                                              :> ("lines"
                                                  :> (QueryParam' '[Required] "logId" (Id "log")
                                                      :> (QueryParam' '[Optional] "iMin" Int
                                                          :> (Auth '[JWT] ()
                                                              :> Get '[JSON] Log))))))))))
                         :<|> (Summary
                                 "Cancel the effect. It will cause the Job to have a failed status."
                               :> ("jobs"
                                   :> (Capture "jobId" (Id Job)
                                       :> ("effects"
                                           :> (Capture "attribute" AttributePath
                                               :> ("cancel"
                                                   :> (Auth '[JWT] ()
                                                       :> Post '[JSON] NoContent))))))))))
            :<|> ((((Summary "Get all organizations user has admin access to"
                     :> (Auth '[JWT] ()
                         :> ("api" :> ("organizations" :> Get '[JSON] [Organization]))))
                    :<|> (Summary "Create a new organization"
                          :> (Auth '[JWT] ()
                              :> ("api"
                                  :> ("organizations"
                                      :> (ReqBody '[JSON] CreateOrganization
                                          :> Post '[JSON] Organization))))))
                   :<|> ((Summary "Connect an account to an organization"
                          :> (Auth '[JWT] ()
                              :> ("api"
                                  :> ("organizations"
                                      :> (Capture "organizationId" (Id Organization)
                                          :> ("accounts"
                                              :> (Capture' '[] "accountId" (Id Account)
                                                  :> Post '[JSON] NoContent)))))))
                         :<|> ((Summary "Generate payment link for an organization"
                                :> (Auth '[JWT] ()
                                    :> ("api"
                                        :> ("organizations"
                                            :> (Capture "organizationId" (Id Organization)
                                                :> ("paymentLink" :> Post '[JSON] PaymentLink))))))
                               :<|> (Summary
                                       "List the active users in an organization's accounts."
                                     :> (Auth '[JWT] ()
                                         :> ("api"
                                             :> ("organizations"
                                                 :> (Capture "organizationId" (Id Organization)
                                                     :> ("billing"
                                                         :> Get '[JSON] BillingInfo)))))))))
                  :<|> ((("projects"
                          :> (Capture' '[Required, Strict] "projectId" (Id Project)
                              :> (((Summary "Upload a state file"
                                    :> ("state"
                                        :> (Capture' '[Required, Strict] "stateName" Text
                                            :> ("data"
                                                :> (StreamBody
                                                      NoFraming OctetStream (SourceIO RawBytes)
                                                    :> (Auth '[JWT] ()
                                                        :> Put '[JSON] NoContent))))))
                                   :<|> (Summary "List all state files"
                                         :> ("states"
                                             :> (Auth '[JWT] () :> Get '[JSON] ProjectState))))
                                  :<|> ((Summary "Download a state file"
                                         :> ("state"
                                             :> (Capture' '[Required, Strict] "stateName" Text
                                                 :> ("data"
                                                     :> (QueryParam'
                                                           '[Optional, Strict] "version" Int
                                                         :> (Auth '[JWT] ()
                                                             :> StreamGet
                                                                  NoFraming
                                                                  OctetStream
                                                                  (Headers
                                                                     '[ContentLength,
                                                                       ContentDisposition]
                                                                     (SourceIO RawBytes))))))))
                                        :<|> (Summary "Acquire a lock"
                                              :> ("lock"
                                                  :> (Capture' '[Required, Strict] "lockName" Text
                                                      :> (ReqBody '[JSON] StateLockAcquireRequest
                                                          :> (Auth '[JWT] ()
                                                              :> Post
                                                                   '[JSON]
                                                                   StateLockAcquireResponse)))))))))
                         :<|> ("site"
                               :> (Capture' '[Required, Strict] "site" (Name SourceHostingSite)
                                   :> ("account"
                                       :> (Capture' '[Required, Strict] "account" (Name Account)
                                           :> ("project"
                                               :> (Capture'
                                                     '[Required, Strict] "project" (Name Project)
                                                   :> (((Summary "Upload a state file"
                                                         :> ("state"
                                                             :> (Capture'
                                                                   '[Required, Strict]
                                                                   "stateName"
                                                                   Text
                                                                 :> ("data"
                                                                     :> (StreamBody
                                                                           NoFraming
                                                                           OctetStream
                                                                           (SourceIO RawBytes)
                                                                         :> (Auth '[JWT] ()
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  NoContent))))))
                                                        :<|> (Summary "List all state files"
                                                              :> ("states"
                                                                  :> (Auth '[JWT] ()
                                                                      :> Get
                                                                           '[JSON] ProjectState))))
                                                       :<|> ((Summary "Download a state file"
                                                              :> ("state"
                                                                  :> (Capture'
                                                                        '[Required, Strict]
                                                                        "stateName"
                                                                        Text
                                                                      :> ("data"
                                                                          :> (QueryParam'
                                                                                '[Optional, Strict]
                                                                                "version"
                                                                                Int
                                                                              :> (Auth '[JWT] ()
                                                                                  :> StreamGet
                                                                                       NoFraming
                                                                                       OctetStream
                                                                                       (Headers
                                                                                          '[ContentLength,
                                                                                            ContentDisposition]
                                                                                          (SourceIO
                                                                                             RawBytes))))))))
                                                             :<|> (Summary "Acquire a lock"
                                                                   :> ("lock"
                                                                       :> (Capture'
                                                                             '[Required, Strict]
                                                                             "lockName"
                                                                             Text
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 StateLockAcquireRequest
                                                                               :> (Auth '[JWT] ()
                                                                                   :> Post
                                                                                        '[JSON]
                                                                                        StateLockAcquireResponse))))))))))))))
                        :<|> (("lock-leases"
                               :> (Capture'
                                     '[Required, Strict] "lockLeaseId" (Id "StateLockLease")
                                   :> (ReqBody '[JSON] StateLockUpdateRequest
                                       :> (Auth '[JWT] ()
                                           :> Post '[JSON] StateLockAcquiredResponse))))
                              :<|> ("lock-leases"
                                    :> (Capture'
                                          '[Required, Strict] "lockLeaseId" (Id "StateLockLease")
                                        :> (Auth '[JWT] () :> Delete '[JSON] NoContent)))))))))
-> Swagger
forall {k} (api :: k). HasSwagger api => Proxy api -> Swagger
toSwagger (forall auth. Proxy (ClientServantAPI auth)
servantClientApi @(Auth '[JWT] ()))
    Swagger -> (Swagger -> Swagger) -> Swagger
forall a b. a -> (a -> b) -> b
& (Info -> Identity Info) -> Swagger -> Identity Swagger
forall s a. HasInfo s a => Lens' s a
info
      ((Info -> Identity Info) -> Swagger -> Identity Swagger)
-> ((Text -> Identity Text) -> Info -> Identity Info)
-> (Text -> Identity Text)
-> Swagger
-> Identity Swagger
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Identity Text) -> Info -> Identity Info
forall s a. HasTitle s a => Lens' s a
title
    ((Text -> Identity Text) -> Swagger -> Identity Swagger)
-> Text -> Swagger -> Swagger
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
"Hercules CI API"
    Swagger -> (Swagger -> Swagger) -> Swagger
forall a b. a -> (a -> b) -> b
& (Info -> Identity Info) -> Swagger -> Identity Swagger
forall s a. HasInfo s a => Lens' s a
info
      ((Info -> Identity Info) -> Swagger -> Identity Swagger)
-> ((Text -> Identity Text) -> Info -> Identity Info)
-> (Text -> Identity Text)
-> Swagger
-> Identity Swagger
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Identity Text) -> Info -> Identity Info
forall s a. HasVersion s a => Lens' s a
version
    ((Text -> Identity Text) -> Swagger -> Identity Swagger)
-> Text -> Swagger -> Swagger
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
"v1"
    Swagger -> (Swagger -> Swagger) -> Swagger
forall a b. a -> (a -> b) -> b
& (Info -> Identity Info) -> Swagger -> Identity Swagger
forall s a. HasInfo s a => Lens' s a
info
      ((Info -> Identity Info) -> Swagger -> Identity Swagger)
-> ((Maybe Text -> Identity (Maybe Text)) -> Info -> Identity Info)
-> (Maybe Text -> Identity (Maybe Text))
-> Swagger
-> Identity Swagger
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Text -> Identity (Maybe Text)) -> Info -> Identity Info
forall s a. HasDescription s a => Lens' s a
description
    ((Maybe Text -> Identity (Maybe Text))
 -> Swagger -> Identity Swagger)
-> Text -> Swagger -> Swagger
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"

-- | 'Control.Monad.void' specialised to 'NoContent' to soothe the
-- compiler that rightfully warns about throwing away a do notation
-- result. By specialising, we make sure that we still get warnings
-- if the result type changes in the future. (We'll get an error)
noContent :: Functor m => m Servant.API.NoContent -> m ()
noContent :: forall (m :: * -> *). Functor m => m NoContent -> m ()
noContent = m NoContent -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void