{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -O0 #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Hercules.CLI.Client where

-- TODO https://github.com/haskell-servant/servant/issues/986

import Data.Has (Has, getter)
import qualified Data.Text as T
import Hercules.API (ClientAPI (..), ClientAuth, servantClientApi, useApi)
import Hercules.API.Accounts (AccountsAPI)
import Hercules.API.Projects (ProjectsAPI)
import Hercules.API.Repos (ReposAPI)
import Hercules.API.State (ContentDisposition, ContentLength, RawBytes, StateAPI)
import Hercules.Error
import qualified Network.HTTP.Client.TLS
import Network.HTTP.Types.Status
import Protolude
import RIO (RIO)
import Servant.API
import Servant.API.Generic
import Servant.Auth.Client (Token)
import qualified Servant.Client
import Servant.Client.Core (ClientError, ResponseF)
import qualified Servant.Client.Core as Client
import qualified Servant.Client.Core.ClientError as ClientError
import Servant.Client.Generic (AsClientT)
import Servant.Client.Streaming (ClientM, responseStatusCode, showBaseUrl)
import qualified Servant.Client.Streaming
import qualified System.Environment

-- | Bad instance to make it the client for State api compile. GHC seems to pick
-- the wrong overlappable instance.
instance
  FromSourceIO
    RawBytes
    ( Headers
        '[ContentLength, ContentDisposition]
        (SourceIO RawBytes)
    )
  where
  fromSourceIO :: SourceIO RawBytes
-> Headers '[ContentLength, ContentDisposition] (SourceIO RawBytes)
fromSourceIO = Integer
-> Headers '[ContentDisposition] (SourceIO RawBytes)
-> Headers '[ContentLength, ContentDisposition] (SourceIO RawBytes)
forall (h :: Symbol) v orig new.
AddHeader h v orig new =>
v -> orig -> new
addHeader (-Integer
1) (Headers '[ContentDisposition] (SourceIO RawBytes)
 -> Headers
      '[ContentLength, ContentDisposition] (SourceIO RawBytes))
-> (SourceIO RawBytes
    -> Headers '[ContentDisposition] (SourceIO RawBytes))
-> SourceIO RawBytes
-> Headers '[ContentLength, ContentDisposition] (SourceIO RawBytes)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text
-> SourceIO RawBytes
-> Headers '[ContentDisposition] (SourceIO RawBytes)
forall (h :: Symbol) v orig new.
AddHeader h v orig new =>
v -> orig -> new
addHeader Text
"" (SourceIO RawBytes
 -> Headers '[ContentDisposition] (SourceIO RawBytes))
-> (SourceIO RawBytes -> SourceIO RawBytes)
-> SourceIO RawBytes
-> Headers '[ContentDisposition] (SourceIO RawBytes)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SourceIO RawBytes -> SourceIO RawBytes
forall chunk a. FromSourceIO chunk a => SourceIO chunk -> a
fromSourceIO

client :: ClientAPI ClientAuth (AsClientT ClientM)
client :: ClientAPI ClientAuth (AsClientT ClientM)
client = ToServant (ClientAPI ClientAuth) (AsClientT ClientM)
-> ClientAPI ClientAuth (AsClientT ClientM)
forall (routes :: * -> *) mode.
GenericServant routes mode =>
ToServant routes mode -> routes mode
fromServant (ToServant (ClientAPI ClientAuth) (AsClientT ClientM)
 -> ClientAPI ClientAuth (AsClientT ClientM))
-> ToServant (ClientAPI ClientAuth) (AsClientT ClientM)
-> ClientAPI ClientAuth (AsClientT ClientM)
forall a b. (a -> b) -> a -> b
$ Proxy
  (AddAPIVersion
     ((((((("accounts"
            :> ("me"
                :> (((Summary "Get the account."
                      :> (ClientAuth :> Get '[JSON] Account))
                     :<|> (Summary "Get the account settings."
                           :> ("settings" :> (ClientAuth :> Get '[JSON] AccountSettings))))
                    :<|> ((Summary "Update the account settings."
                           :> ("settings"
                               :> (ReqBody '[JSON] AccountSettingsPatch
                                   :> (ClientAuth :> Patch '[JSON] AccountSettings))))
                          :<|> (Summary "Disable all projects in the account."
                                :> ("disable-all-projects"
                                    :> (ClientAuth :> Post '[JSON] Int)))))))
           :<|> ((Summary "Retrieve notification settings"
                  :> ("accounts"
                      :> ("me"
                          :> ("settings"
                              :> ("notifications"
                                  :> (ClientAuth :> Get '[JSON] NotificationSettings))))))
                 :<|> (Summary "Update notification settings"
                       :> ("accounts"
                           :> ("me"
                               :> ("settings"
                                   :> ("notifications"
                                       :> (ReqBody '[JSON] NotificationSettingsPatch
                                           :> (ClientAuth
                                               :> Patch '[JSON] NotificationSettings)))))))))
          :<|> (("accounts"
                 :> (Capture' '[] "accountId" (Id Account)
                     :> (((Summary "Get the account."
                           :> (ClientAuth :> Get '[JSON] Account))
                          :<|> (Summary "Get the account settings."
                                :> ("settings" :> (ClientAuth :> Get '[JSON] AccountSettings))))
                         :<|> ((Summary "Update the account settings."
                                :> ("settings"
                                    :> (ReqBody '[JSON] AccountSettingsPatch
                                        :> (ClientAuth :> Patch '[JSON] AccountSettings))))
                               :<|> (Summary "Disable all projects in the account."
                                     :> ("disable-all-projects"
                                         :> (ClientAuth :> Post '[JSON] Int)))))))
                :<|> (("site"
                       :> (Capture' '[] "site" (Name SourceHostingSite)
                           :> ("account"
                               :> (Capture' '[] "account" (Name Account)
                                   :> (((Summary "Get the account."
                                         :> (ClientAuth :> Get '[JSON] Account))
                                        :<|> (Summary "Get the account settings."
                                              :> ("settings"
                                                  :> (ClientAuth :> Get '[JSON] AccountSettings))))
                                       :<|> ((Summary "Update the account settings."
                                              :> ("settings"
                                                  :> (ReqBody '[JSON] AccountSettingsPatch
                                                      :> (ClientAuth
                                                          :> Patch '[JSON] AccountSettings))))
                                             :<|> (Summary "Disable all projects in the account."
                                                   :> ("disable-all-projects"
                                                       :> (ClientAuth :> Post '[JSON] Int)))))))))
                      :<|> (Summary
                              "Accounts that the authenticated user owns, admins or collaborates with."
                            :> ("accounts"
                                :> (QueryParam "site" (Name SourceHostingSite)
                                    :> (QueryParam "name" (Name Account)
                                        :> (ClientAuth :> 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
                                                :> (ClientAuth
                                                    :> Get '[JSON] CLIAuthorizationRequest)))))))))
               :<|> (((Summary "Retrieve the request"
                       :> ("auth"
                           :> ("cli"
                               :> ("authorization"
                                   :> ("request"
                                       :> (Capture "browserToken" Text
                                           :> ("confirm"
                                               :> (ClientAuth :> Post '[JSON] NoContent))))))))
                      :<|> (Summary
                              "List the CLI tokens associated with the current account."
                            :> ("auth"
                                :> ("cli"
                                    :> ("tokens"
                                        :> (ClientAuth :> Get '[JSON] CLITokensResponse))))))
                     :<|> ((Summary "Permanently disallow the use of a CLI token."
                            :> ("auth"
                                :> ("cli"
                                    :> ("tokens"
                                        :> (Capture "cliTokenId" (Id "CLIToken")
                                            :> ("revoke"
                                                :> (ClientAuth :> Post '[JSON] NoContent)))))))
                           :<|> (Summary
                                   "Retrieve installation status after redirect from external source site settings."
                                 :> ("sites"
                                     :> (Capture "siteId" (Id SourceHostingSite)
                                         :> ("installation"
                                             :> (Capture "installationId" Int
                                                 :> ("status"
                                                     :> (ClientAuth
                                                         :> Get
                                                              '[JSON]
                                                              AccountInstallationStatus)))))))))))
        :<|> ((Summary
                 "Repositories that the account owns or has explicit access to."
               :> ("accounts"
                   :> (Capture' '[Required, Strict] "accountId" (Id Account)
                       :> ("repos" :> (ClientAuth :> 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
                            :> (ClientAuth :> 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)
                                          :> (ClientAuth :> 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
                                               :> (ClientAuth
                                                   :> 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)
                                                                :> (ClientAuth
                                                                    :> 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
                                                                     :> (ClientAuth
                                                                         :> Get
                                                                              '[JSON]
                                                                              ImmutableGitInput)))))))))))))
                      :<|> (Summary "List all projects owned by an account."
                            :> ("accounts"
                                :> (Capture' '[Required, Strict] "accountId" (Id Account)
                                    :> ("projects" :> (ClientAuth :> Get '[JSON] [Project])))))))
               :<|> ((Summary "Find projects"
                      :> ("projects"
                          :> (QueryParam' '[Optional] "site" (Name SourceHostingSite)
                              :> (QueryParam' '[Optional] "account" (Name Account)
                                  :> (QueryParam' '[Optional] "project" (Name Project)
                                      :> (ClientAuth :> Get '[JSON] [Project]))))))
                     :<|> ((Summary "Create a new project."
                            :> ("projects"
                                :> (ClientAuth
                                    :> (ReqBody '[JSON] CreateProject
                                        :> Post '[JSON] (Id Project)))))
                           :<|> (Summary "Modify a project"
                                 :> ("projects"
                                     :> (Capture' '[Required, Strict] "projectId" (Id Project)
                                         :> (ReqBody '[JSON] PatchProject
                                             :> (ClientAuth :> Patch '[JSON] Project))))))))
              :<|> (((Summary "Create a token for local effect execution"
                      :> ("projects"
                          :> (Capture' '[Required, Strict] "projectId" (Id Project)
                              :> (ClientAuth
                                  :> ("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
                                                    :> (ClientAuth
                                                        :> 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"
                                                 :> (ClientAuth
                                                     :> 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" :> (ClientAuth :> 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
                                                     :> (ClientAuth :> 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"
                                                 :> (ClientAuth :> 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
                                                                  :> (ClientAuth
                                                                      :> Get
                                                                           '[JSON] Log)))))))))))))
             :<|> (((Summary "List all cluster join tokens in an account."
                     :> ("accounts"
                         :> (Capture' '[Required, Strict] "accountId" (Id Account)
                             :> ("clusterJoinTokens"
                                 :> (ClientAuth :> 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
                                          :> (ClientAuth :> 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)
                                          :> (ClientAuth :> Delete '[JSON] NoContent))))))
                         :<|> (Summary "Show the agents sessions owned by the account."
                               :> ("accounts"
                                   :> (Capture' '[Required, Strict] "accountId" (Id Account)
                                       :> ("agentSessions"
                                           :> (ClientAuth :> Get '[JSON] [AgentSession])))))))))
      :<|> (((((Summary "Restart a derivation"
                :> ("accounts"
                    :> (Capture' '[] "accountId" (Id Account)
                        :> ("derivations"
                            :> (Capture "derivationPath" Text
                                :> ("retry"
                                    :> (ClientAuth :> 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")
                                                 :> (ClientAuth
                                                     :> 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
                                                     :> (ClientAuth :> 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)
                                                  :> (ClientAuth
                                                      :> Get '[JSON] DerivationInfo))))))))))
             :<|> ((Summary "Read effect events"
                    :> ("jobs"
                        :> (Capture "jobId" (Id Job)
                            :> ("effects"
                                :> (Capture "attribute" AttributePath
                                    :> (ClientAuth :> 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
                                                          :> (ClientAuth
                                                              :> 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"
                                                   :> (ClientAuth
                                                       :> Post '[JSON] NoContent))))))))))
            :<|> ((((Summary "Get all organizations user has admin access to"
                     :> (ClientAuth
                         :> ("api" :> ("organizations" :> Get '[JSON] [Organization]))))
                    :<|> (Summary "Create a new organization"
                          :> (ClientAuth
                              :> ("api"
                                  :> ("organizations"
                                      :> (ReqBody '[JSON] CreateOrganization
                                          :> Post '[JSON] Organization))))))
                   :<|> ((Summary "Connect an account to an organization"
                          :> (ClientAuth
                              :> ("api"
                                  :> ("organizations"
                                      :> (Capture "organizationId" (Id Organization)
                                          :> ("accounts"
                                              :> (Capture' '[] "accountId" (Id Account)
                                                  :> Post '[JSON] NoContent)))))))
                         :<|> ((Summary "Generate payment link for an organization"
                                :> (ClientAuth
                                    :> ("api"
                                        :> ("organizations"
                                            :> (Capture "organizationId" (Id Organization)
                                                :> ("paymentLink" :> Post '[JSON] PaymentLink))))))
                               :<|> (Summary
                                       "List the active users in an organization's accounts."
                                     :> (ClientAuth
                                         :> ("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)
                                                    :> (ClientAuth :> Put '[JSON] NoContent))))))
                                   :<|> (Summary "List all state files"
                                         :> ("states" :> (ClientAuth :> Get '[JSON] ProjectState))))
                                  :<|> ((Summary "Download a state file"
                                         :> ("state"
                                             :> (Capture' '[Required, Strict] "stateName" Text
                                                 :> ("data"
                                                     :> (QueryParam'
                                                           '[Optional, Strict] "version" Int
                                                         :> (ClientAuth
                                                             :> StreamGet
                                                                  NoFraming
                                                                  OctetStream
                                                                  (Headers
                                                                     '[ContentLength,
                                                                       ContentDisposition]
                                                                     (SourceIO RawBytes))))))))
                                        :<|> (Summary "Acquire a lock"
                                              :> ("lock"
                                                  :> (Capture' '[Required, Strict] "lockName" Text
                                                      :> (ReqBody '[JSON] StateLockAcquireRequest
                                                          :> (ClientAuth
                                                              :> 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)
                                                                         :> (ClientAuth
                                                                             :> Put
                                                                                  '[JSON]
                                                                                  NoContent))))))
                                                        :<|> (Summary "List all state files"
                                                              :> ("states"
                                                                  :> (ClientAuth
                                                                      :> Get
                                                                           '[JSON] ProjectState))))
                                                       :<|> ((Summary "Download a state file"
                                                              :> ("state"
                                                                  :> (Capture'
                                                                        '[Required, Strict]
                                                                        "stateName"
                                                                        Text
                                                                      :> ("data"
                                                                          :> (QueryParam'
                                                                                '[Optional, Strict]
                                                                                "version"
                                                                                Int
                                                                              :> (ClientAuth
                                                                                  :> StreamGet
                                                                                       NoFraming
                                                                                       OctetStream
                                                                                       (Headers
                                                                                          '[ContentLength,
                                                                                            ContentDisposition]
                                                                                          (SourceIO
                                                                                             RawBytes))))))))
                                                             :<|> (Summary "Acquire a lock"
                                                                   :> ("lock"
                                                                       :> (Capture'
                                                                             '[Required, Strict]
                                                                             "lockName"
                                                                             Text
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 StateLockAcquireRequest
                                                                               :> (ClientAuth
                                                                                   :> Post
                                                                                        '[JSON]
                                                                                        StateLockAcquireResponse))))))))))))))
                        :<|> (("lock-leases"
                               :> (Capture'
                                     '[Required, Strict] "lockLeaseId" (Id "StateLockLease")
                                   :> (ReqBody '[JSON] StateLockUpdateRequest
                                       :> (ClientAuth :> Post '[JSON] StateLockAcquiredResponse))))
                              :<|> ("lock-leases"
                                    :> (Capture'
                                          '[Required, Strict] "lockLeaseId" (Id "StateLockLease")
                                        :> (ClientAuth :> Delete '[JSON] NoContent)))))))))
-> Client
     ClientM
     (AddAPIVersion
        ((((((("accounts"
               :> ("me"
                   :> (((Summary "Get the account."
                         :> (ClientAuth :> Get '[JSON] Account))
                        :<|> (Summary "Get the account settings."
                              :> ("settings" :> (ClientAuth :> Get '[JSON] AccountSettings))))
                       :<|> ((Summary "Update the account settings."
                              :> ("settings"
                                  :> (ReqBody '[JSON] AccountSettingsPatch
                                      :> (ClientAuth :> Patch '[JSON] AccountSettings))))
                             :<|> (Summary "Disable all projects in the account."
                                   :> ("disable-all-projects"
                                       :> (ClientAuth :> Post '[JSON] Int)))))))
              :<|> ((Summary "Retrieve notification settings"
                     :> ("accounts"
                         :> ("me"
                             :> ("settings"
                                 :> ("notifications"
                                     :> (ClientAuth :> Get '[JSON] NotificationSettings))))))
                    :<|> (Summary "Update notification settings"
                          :> ("accounts"
                              :> ("me"
                                  :> ("settings"
                                      :> ("notifications"
                                          :> (ReqBody '[JSON] NotificationSettingsPatch
                                              :> (ClientAuth
                                                  :> Patch '[JSON] NotificationSettings)))))))))
             :<|> (("accounts"
                    :> (Capture' '[] "accountId" (Id Account)
                        :> (((Summary "Get the account."
                              :> (ClientAuth :> Get '[JSON] Account))
                             :<|> (Summary "Get the account settings."
                                   :> ("settings" :> (ClientAuth :> Get '[JSON] AccountSettings))))
                            :<|> ((Summary "Update the account settings."
                                   :> ("settings"
                                       :> (ReqBody '[JSON] AccountSettingsPatch
                                           :> (ClientAuth :> Patch '[JSON] AccountSettings))))
                                  :<|> (Summary "Disable all projects in the account."
                                        :> ("disable-all-projects"
                                            :> (ClientAuth :> Post '[JSON] Int)))))))
                   :<|> (("site"
                          :> (Capture' '[] "site" (Name SourceHostingSite)
                              :> ("account"
                                  :> (Capture' '[] "account" (Name Account)
                                      :> (((Summary "Get the account."
                                            :> (ClientAuth :> Get '[JSON] Account))
                                           :<|> (Summary "Get the account settings."
                                                 :> ("settings"
                                                     :> (ClientAuth
                                                         :> Get '[JSON] AccountSettings))))
                                          :<|> ((Summary "Update the account settings."
                                                 :> ("settings"
                                                     :> (ReqBody '[JSON] AccountSettingsPatch
                                                         :> (ClientAuth
                                                             :> Patch '[JSON] AccountSettings))))
                                                :<|> (Summary "Disable all projects in the account."
                                                      :> ("disable-all-projects"
                                                          :> (ClientAuth
                                                              :> Post '[JSON] Int)))))))))
                         :<|> (Summary
                                 "Accounts that the authenticated user owns, admins or collaborates with."
                               :> ("accounts"
                                   :> (QueryParam "site" (Name SourceHostingSite)
                                       :> (QueryParam "name" (Name Account)
                                           :> (ClientAuth :> 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
                                                   :> (ClientAuth
                                                       :> Get
                                                            '[JSON] CLIAuthorizationRequest)))))))))
                  :<|> (((Summary "Retrieve the request"
                          :> ("auth"
                              :> ("cli"
                                  :> ("authorization"
                                      :> ("request"
                                          :> (Capture "browserToken" Text
                                              :> ("confirm"
                                                  :> (ClientAuth :> Post '[JSON] NoContent))))))))
                         :<|> (Summary
                                 "List the CLI tokens associated with the current account."
                               :> ("auth"
                                   :> ("cli"
                                       :> ("tokens"
                                           :> (ClientAuth :> Get '[JSON] CLITokensResponse))))))
                        :<|> ((Summary "Permanently disallow the use of a CLI token."
                               :> ("auth"
                                   :> ("cli"
                                       :> ("tokens"
                                           :> (Capture "cliTokenId" (Id "CLIToken")
                                               :> ("revoke"
                                                   :> (ClientAuth :> Post '[JSON] NoContent)))))))
                              :<|> (Summary
                                      "Retrieve installation status after redirect from external source site settings."
                                    :> ("sites"
                                        :> (Capture "siteId" (Id SourceHostingSite)
                                            :> ("installation"
                                                :> (Capture "installationId" Int
                                                    :> ("status"
                                                        :> (ClientAuth
                                                            :> Get
                                                                 '[JSON]
                                                                 AccountInstallationStatus)))))))))))
           :<|> ((Summary
                    "Repositories that the account owns or has explicit access to."
                  :> ("accounts"
                      :> (Capture' '[Required, Strict] "accountId" (Id Account)
                          :> ("repos" :> (ClientAuth :> 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
                               :> (ClientAuth :> 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)
                                             :> (ClientAuth :> 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
                                                  :> (ClientAuth
                                                      :> 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)
                                                                   :> (ClientAuth
                                                                       :> 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
                                                                        :> (ClientAuth
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 ImmutableGitInput)))))))))))))
                         :<|> (Summary "List all projects owned by an account."
                               :> ("accounts"
                                   :> (Capture' '[Required, Strict] "accountId" (Id Account)
                                       :> ("projects" :> (ClientAuth :> Get '[JSON] [Project])))))))
                  :<|> ((Summary "Find projects"
                         :> ("projects"
                             :> (QueryParam' '[Optional] "site" (Name SourceHostingSite)
                                 :> (QueryParam' '[Optional] "account" (Name Account)
                                     :> (QueryParam' '[Optional] "project" (Name Project)
                                         :> (ClientAuth :> Get '[JSON] [Project]))))))
                        :<|> ((Summary "Create a new project."
                               :> ("projects"
                                   :> (ClientAuth
                                       :> (ReqBody '[JSON] CreateProject
                                           :> Post '[JSON] (Id Project)))))
                              :<|> (Summary "Modify a project"
                                    :> ("projects"
                                        :> (Capture' '[Required, Strict] "projectId" (Id Project)
                                            :> (ReqBody '[JSON] PatchProject
                                                :> (ClientAuth :> Patch '[JSON] Project))))))))
                 :<|> (((Summary "Create a token for local effect execution"
                         :> ("projects"
                             :> (Capture' '[Required, Strict] "projectId" (Id Project)
                                 :> (ClientAuth
                                     :> ("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
                                                       :> (ClientAuth
                                                           :> 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"
                                                    :> (ClientAuth
                                                        :> 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"
                                                   :> (ClientAuth :> 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
                                                        :> (ClientAuth :> 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"
                                                    :> (ClientAuth :> 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
                                                                     :> (ClientAuth
                                                                         :> Get
                                                                              '[JSON]
                                                                              Log)))))))))))))
                :<|> (((Summary "List all cluster join tokens in an account."
                        :> ("accounts"
                            :> (Capture' '[Required, Strict] "accountId" (Id Account)
                                :> ("clusterJoinTokens"
                                    :> (ClientAuth :> 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
                                             :> (ClientAuth
                                                 :> 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)
                                             :> (ClientAuth :> Delete '[JSON] NoContent))))))
                            :<|> (Summary "Show the agents sessions owned by the account."
                                  :> ("accounts"
                                      :> (Capture' '[Required, Strict] "accountId" (Id Account)
                                          :> ("agentSessions"
                                              :> (ClientAuth :> Get '[JSON] [AgentSession])))))))))
         :<|> (((((Summary "Restart a derivation"
                   :> ("accounts"
                       :> (Capture' '[] "accountId" (Id Account)
                           :> ("derivations"
                               :> (Capture "derivationPath" Text
                                   :> ("retry"
                                       :> (ClientAuth :> 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")
                                                    :> (ClientAuth
                                                        :> 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
                                                        :> (ClientAuth :> 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)
                                                     :> (ClientAuth
                                                         :> Get '[JSON] DerivationInfo))))))))))
                :<|> ((Summary "Read effect events"
                       :> ("jobs"
                           :> (Capture "jobId" (Id Job)
                               :> ("effects"
                                   :> (Capture "attribute" AttributePath
                                       :> (ClientAuth :> 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
                                                             :> (ClientAuth
                                                                 :> 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"
                                                      :> (ClientAuth
                                                          :> Post '[JSON] NoContent))))))))))
               :<|> ((((Summary "Get all organizations user has admin access to"
                        :> (ClientAuth
                            :> ("api" :> ("organizations" :> Get '[JSON] [Organization]))))
                       :<|> (Summary "Create a new organization"
                             :> (ClientAuth
                                 :> ("api"
                                     :> ("organizations"
                                         :> (ReqBody '[JSON] CreateOrganization
                                             :> Post '[JSON] Organization))))))
                      :<|> ((Summary "Connect an account to an organization"
                             :> (ClientAuth
                                 :> ("api"
                                     :> ("organizations"
                                         :> (Capture "organizationId" (Id Organization)
                                             :> ("accounts"
                                                 :> (Capture' '[] "accountId" (Id Account)
                                                     :> Post '[JSON] NoContent)))))))
                            :<|> ((Summary "Generate payment link for an organization"
                                   :> (ClientAuth
                                       :> ("api"
                                           :> ("organizations"
                                               :> (Capture "organizationId" (Id Organization)
                                                   :> ("paymentLink"
                                                       :> Post '[JSON] PaymentLink))))))
                                  :<|> (Summary
                                          "List the active users in an organization's accounts."
                                        :> (ClientAuth
                                            :> ("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)
                                                       :> (ClientAuth :> Put '[JSON] NoContent))))))
                                      :<|> (Summary "List all state files"
                                            :> ("states"
                                                :> (ClientAuth :> Get '[JSON] ProjectState))))
                                     :<|> ((Summary "Download a state file"
                                            :> ("state"
                                                :> (Capture' '[Required, Strict] "stateName" Text
                                                    :> ("data"
                                                        :> (QueryParam'
                                                              '[Optional, Strict] "version" Int
                                                            :> (ClientAuth
                                                                :> StreamGet
                                                                     NoFraming
                                                                     OctetStream
                                                                     (Headers
                                                                        '[ContentLength,
                                                                          ContentDisposition]
                                                                        (SourceIO RawBytes))))))))
                                           :<|> (Summary "Acquire a lock"
                                                 :> ("lock"
                                                     :> (Capture'
                                                           '[Required, Strict] "lockName" Text
                                                         :> (ReqBody '[JSON] StateLockAcquireRequest
                                                             :> (ClientAuth
                                                                 :> 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)
                                                                            :> (ClientAuth
                                                                                :> Put
                                                                                     '[JSON]
                                                                                     NoContent))))))
                                                           :<|> (Summary "List all state files"
                                                                 :> ("states"
                                                                     :> (ClientAuth
                                                                         :> Get
                                                                              '[JSON]
                                                                              ProjectState))))
                                                          :<|> ((Summary "Download a state file"
                                                                 :> ("state"
                                                                     :> (Capture'
                                                                           '[Required, Strict]
                                                                           "stateName"
                                                                           Text
                                                                         :> ("data"
                                                                             :> (QueryParam'
                                                                                   '[Optional,
                                                                                     Strict]
                                                                                   "version"
                                                                                   Int
                                                                                 :> (ClientAuth
                                                                                     :> StreamGet
                                                                                          NoFraming
                                                                                          OctetStream
                                                                                          (Headers
                                                                                             '[ContentLength,
                                                                                               ContentDisposition]
                                                                                             (SourceIO
                                                                                                RawBytes))))))))
                                                                :<|> (Summary "Acquire a lock"
                                                                      :> ("lock"
                                                                          :> (Capture'
                                                                                '[Required, Strict]
                                                                                "lockName"
                                                                                Text
                                                                              :> (ReqBody
                                                                                    '[JSON]
                                                                                    StateLockAcquireRequest
                                                                                  :> (ClientAuth
                                                                                      :> Post
                                                                                           '[JSON]
                                                                                           StateLockAcquireResponse))))))))))))))
                           :<|> (("lock-leases"
                                  :> (Capture'
                                        '[Required, Strict] "lockLeaseId" (Id "StateLockLease")
                                      :> (ReqBody '[JSON] StateLockUpdateRequest
                                          :> (ClientAuth
                                              :> Post '[JSON] StateLockAcquiredResponse))))
                                 :<|> ("lock-leases"
                                       :> (Capture'
                                             '[Required, Strict] "lockLeaseId" (Id "StateLockLease")
                                           :> (ClientAuth :> Delete '[JSON] NoContent)))))))))
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
Servant.Client.Streaming.client (forall auth. Proxy (ClientServantAPI auth)
servantClientApi @ClientAuth)

accountsClient :: AccountsAPI ClientAuth (AsClientT ClientM)
accountsClient :: AccountsAPI ClientAuth (AsClientT ClientM)
accountsClient = (ClientAPI ClientAuth (AsClientT ClientM)
 -> ToServant (AccountsAPI ClientAuth) (AsClientT ClientM))
-> ClientAPI ClientAuth (AsClientT ClientM)
-> AccountsAPI ClientAuth (AsClientT ClientM)
forall (subapi :: * -> *) (api :: * -> *) mode.
(GenericServant api mode, GenericServant subapi mode) =>
(api mode -> ToServant subapi mode) -> api mode -> subapi mode
useApi ClientAPI ClientAuth (AsClientT ClientM)
-> ToServant (AccountsAPI ClientAuth) (AsClientT ClientM)
forall auth f.
ClientAPI auth f -> f :- ToServantApi (AccountsAPI auth)
clientAccounts ClientAPI ClientAuth (AsClientT ClientM)
client

stateClient :: StateAPI ClientAuth (AsClientT ClientM)
stateClient :: StateAPI ClientAuth (AsClientT ClientM)
stateClient = (ClientAPI ClientAuth (AsClientT ClientM)
 -> ToServant (StateAPI ClientAuth) (AsClientT ClientM))
-> ClientAPI ClientAuth (AsClientT ClientM)
-> StateAPI ClientAuth (AsClientT ClientM)
forall (subapi :: * -> *) (api :: * -> *) mode.
(GenericServant api mode, GenericServant subapi mode) =>
(api mode -> ToServant subapi mode) -> api mode -> subapi mode
useApi ClientAPI ClientAuth (AsClientT ClientM)
-> ToServant (StateAPI ClientAuth) (AsClientT ClientM)
forall auth f.
ClientAPI auth f -> f :- ToServantApi (StateAPI auth)
clientState ClientAPI ClientAuth (AsClientT ClientM)
client

projectsClient :: ProjectsAPI ClientAuth (AsClientT ClientM)
projectsClient :: ProjectsAPI ClientAuth (AsClientT ClientM)
projectsClient = (ClientAPI ClientAuth (AsClientT ClientM)
 -> ToServant (ProjectsAPI ClientAuth) (AsClientT ClientM))
-> ClientAPI ClientAuth (AsClientT ClientM)
-> ProjectsAPI ClientAuth (AsClientT ClientM)
forall (subapi :: * -> *) (api :: * -> *) mode.
(GenericServant api mode, GenericServant subapi mode) =>
(api mode -> ToServant subapi mode) -> api mode -> subapi mode
useApi ClientAPI ClientAuth (AsClientT ClientM)
-> ToServant (ProjectsAPI ClientAuth) (AsClientT ClientM)
forall auth f.
ClientAPI auth f -> f :- ToServantApi (ProjectsAPI auth)
clientProjects ClientAPI ClientAuth (AsClientT ClientM)
client

reposClient :: ReposAPI ClientAuth (AsClientT ClientM)
reposClient :: ReposAPI ClientAuth (AsClientT ClientM)
reposClient = (ClientAPI ClientAuth (AsClientT ClientM)
 -> ToServant (ReposAPI ClientAuth) (AsClientT ClientM))
-> ClientAPI ClientAuth (AsClientT ClientM)
-> ReposAPI ClientAuth (AsClientT ClientM)
forall (subapi :: * -> *) (api :: * -> *) mode.
(GenericServant api mode, GenericServant subapi mode) =>
(api mode -> ToServant subapi mode) -> api mode -> subapi mode
useApi ClientAPI ClientAuth (AsClientT ClientM)
-> ToServant (ReposAPI ClientAuth) (AsClientT ClientM)
forall auth f.
ClientAPI auth f -> f :- ToServantApi (ReposAPI auth)
clientRepos ClientAPI ClientAuth (AsClientT ClientM)
client

-- Duplicated from agent... create common lib?
determineDefaultApiBaseUrl :: IO Text
determineDefaultApiBaseUrl :: IO Text
determineDefaultApiBaseUrl = do
  Maybe String
maybeEnv <- String -> IO (Maybe String)
System.Environment.lookupEnv String
"HERCULES_CI_API_BASE_URL"
  Text -> IO Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> IO Text) -> Text -> IO Text
forall a b. (a -> b) -> a -> b
$ Text -> (String -> Text) -> Maybe String -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
defaultApiBaseUrl String -> Text
forall a b. ConvertText a b => a -> b
toS Maybe String
maybeEnv

defaultApiBaseUrl :: Text
defaultApiBaseUrl :: Text
defaultApiBaseUrl = Text
"https://hercules-ci.com"

newtype HerculesClientEnv = HerculesClientEnv Servant.Client.ClientEnv

newtype HerculesClientToken = HerculesClientToken Token

runHerculesClient :: (NFData a, Has HerculesClientToken r, Has HerculesClientEnv r) => (Token -> Servant.Client.Streaming.ClientM a) -> RIO r a
runHerculesClient :: forall a r.
(NFData a, Has HerculesClientToken r, Has HerculesClientEnv r) =>
(Token -> ClientM a) -> RIO r a
runHerculesClient Token -> ClientM a
f = do
  HerculesClientToken Token
token <- (r -> HerculesClientToken) -> RIO r HerculesClientToken
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> HerculesClientToken
forall a t. Has a t => t -> a
getter
  ClientM a -> RIO r a
forall a r.
(NFData a, Has HerculesClientEnv r) =>
ClientM a -> RIO r a
runHerculesClient' (ClientM a -> RIO r a) -> ClientM a -> RIO r a
forall a b. (a -> b) -> a -> b
$ Token -> ClientM a
f Token
token

runHerculesClientEither :: (NFData a, Has HerculesClientToken r, Has HerculesClientEnv r) => (Token -> Servant.Client.Streaming.ClientM a) -> RIO r (Either Servant.Client.Streaming.ClientError a)
runHerculesClientEither :: forall a r.
(NFData a, Has HerculesClientToken r, Has HerculesClientEnv r) =>
(Token -> ClientM a) -> RIO r (Either ClientError a)
runHerculesClientEither Token -> ClientM a
f = do
  HerculesClientToken Token
token <- (r -> HerculesClientToken) -> RIO r HerculesClientToken
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> HerculesClientToken
forall a t. Has a t => t -> a
getter
  ClientM a -> RIO r (Either ClientError a)
forall a r.
(NFData a, Has HerculesClientEnv r) =>
ClientM a -> RIO r (Either ClientError a)
runHerculesClientEither' (ClientM a -> RIO r (Either ClientError a))
-> ClientM a -> RIO r (Either ClientError a)
forall a b. (a -> b) -> a -> b
$ Token -> ClientM a
f Token
token

runHerculesClientStream ::
  (Has HerculesClientToken r, Has HerculesClientEnv r) =>
  (Token -> Servant.Client.Streaming.ClientM a) ->
  (Either Servant.Client.Streaming.ClientError a -> IO b) ->
  RIO r b
runHerculesClientStream :: forall r a b.
(Has HerculesClientToken r, Has HerculesClientEnv r) =>
(Token -> ClientM a) -> (Either ClientError a -> IO b) -> RIO r b
runHerculesClientStream Token -> ClientM a
f Either ClientError a -> IO b
g = do
  HerculesClientToken Token
token <- (r -> HerculesClientToken) -> RIO r HerculesClientToken
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> HerculesClientToken
forall a t. Has a t => t -> a
getter
  HerculesClientEnv ClientEnv
clientEnv <- (r -> HerculesClientEnv) -> RIO r HerculesClientEnv
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> HerculesClientEnv
forall a t. Has a t => t -> a
getter
  IO b -> RIO r b
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO b -> RIO r b) -> IO b -> RIO r b
forall a b. (a -> b) -> a -> b
$ ClientM a -> ClientEnv -> (Either ClientError a -> IO b) -> IO b
forall a b.
ClientM a -> ClientEnv -> (Either ClientError a -> IO b) -> IO b
Servant.Client.Streaming.withClientM (Token -> ClientM a
f Token
token) ClientEnv
clientEnv Either ClientError a -> IO b
g

runHerculesClient' :: (NFData a, Has HerculesClientEnv r) => Servant.Client.Streaming.ClientM a -> RIO r a
runHerculesClient' :: forall a r.
(NFData a, Has HerculesClientEnv r) =>
ClientM a -> RIO r a
runHerculesClient' = ClientM a -> RIO r (Either ClientError a)
forall a r.
(NFData a, Has HerculesClientEnv r) =>
ClientM a -> RIO r (Either ClientError a)
runHerculesClientEither' (ClientM a -> RIO r (Either ClientError a))
-> (Either ClientError a -> RIO r a) -> ClientM a -> RIO r a
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Either ClientError a -> RIO r a
forall exc (m :: * -> *) a.
(Exception exc, MonadThrow m) =>
Either exc a -> m a
escalate

runHerculesClientEither' :: (NFData a, Has HerculesClientEnv r) => Servant.Client.Streaming.ClientM a -> RIO r (Either Servant.Client.Streaming.ClientError a)
runHerculesClientEither' :: forall a r.
(NFData a, Has HerculesClientEnv r) =>
ClientM a -> RIO r (Either ClientError a)
runHerculesClientEither' ClientM a
m = do
  HerculesClientEnv ClientEnv
clientEnv <- (r -> HerculesClientEnv) -> RIO r HerculesClientEnv
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> HerculesClientEnv
forall a t. Has a t => t -> a
getter
  IO (Either ClientError a) -> RIO r (Either ClientError a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (ClientM a -> ClientEnv -> IO (Either ClientError a)
forall a.
NFData a =>
ClientM a -> ClientEnv -> IO (Either ClientError a)
Servant.Client.Streaming.runClientM ClientM a
m ClientEnv
clientEnv)

init :: IO HerculesClientEnv
init :: IO HerculesClientEnv
init = do
  Manager
manager <- IO Manager
forall (m :: * -> *). MonadIO m => m Manager
Network.HTTP.Client.TLS.newTlsManager
  Text
baseUrlText <- IO Text
determineDefaultApiBaseUrl
  BaseUrl
baseUrl <- String -> IO BaseUrl
forall (m :: * -> *). MonadThrow m => String -> m BaseUrl
Servant.Client.parseBaseUrl (String -> IO BaseUrl) -> String -> IO BaseUrl
forall a b. (a -> b) -> a -> b
$ Text -> String
forall a b. ConvertText a b => a -> b
toS Text
baseUrlText
  let clientEnv :: Servant.Client.ClientEnv
      clientEnv :: ClientEnv
clientEnv = Manager -> BaseUrl -> ClientEnv
Servant.Client.mkClientEnv Manager
manager BaseUrl
baseUrl
  HerculesClientEnv -> IO HerculesClientEnv
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HerculesClientEnv -> IO HerculesClientEnv)
-> HerculesClientEnv -> IO HerculesClientEnv
forall a b. (a -> b) -> a -> b
$ ClientEnv -> HerculesClientEnv
HerculesClientEnv ClientEnv
clientEnv

dieWithHttpError :: Client.ClientError -> IO a
dieWithHttpError :: forall a. ClientError -> IO a
dieWithHttpError (Client.FailureResponse RequestF () (BaseUrl, ByteString)
req Response
resp) = do
  let status :: Status
status = Response -> Status
forall a. ResponseF a -> Status
responseStatusCode Response
resp
      (BaseUrl
base, ByteString
path) = RequestF () (BaseUrl, ByteString) -> (BaseUrl, ByteString)
forall body path. RequestF body path -> path
Client.requestPath RequestF () (BaseUrl, ByteString)
req
  Text -> IO ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putErrText (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$
    Text
"hci: Request failed; "
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a b. (Show a, ConvertText String b) => a -> b
show (Status -> Int
statusCode Status
status)
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" "
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode (Status -> ByteString
statusMessage Status
status)
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" on: "
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
forall a b. ConvertText a b => a -> b
toS (BaseUrl -> String
showBaseUrl BaseUrl
base)
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/"
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Char -> Bool) -> Text -> Text
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/') (OnDecodeError -> ByteString -> Text
decodeUtf8With OnDecodeError
lenientDecode ByteString
path)
  IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO a
forall a. IO a
exitFailure
dieWithHttpError ClientError
e = do
  Text -> IO ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putErrText (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
"hci: Request failed: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
forall a b. ConvertText a b => a -> b
toS (ClientError -> String
forall e. Exception e => e -> String
displayException ClientError
e)
  IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO a
forall a. IO a
exitFailure

prettyPrintHttpErrors :: IO a -> IO a
prettyPrintHttpErrors :: forall a. IO a -> IO a
prettyPrintHttpErrors = (ClientError -> IO a) -> IO a -> IO a
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
handle ClientError -> IO a
forall a. ClientError -> IO a
dieWithHttpError

-- | Low indicating the inclusiveness of the boundaries. Low is included. High is excluded.
-- A pair where `fst` > `snd` forms an empty range.
inLowRange :: Ord a => a -> (a, a) -> Bool
a
a inLowRange :: forall a. Ord a => a -> (a, a) -> Bool
`inLowRange` (a
p, a
q) = a
a a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
p Bool -> Bool -> Bool
&& a
a a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
q

-- In a library, this should support 429 with Retry-After
shouldRetryResponse :: Either ClientError r -> Bool
shouldRetryResponse :: forall r. Either ClientError r -> Bool
shouldRetryResponse (Left ClientError
e) = ClientError -> Bool
shouldRetryClientError ClientError
e
shouldRetryResponse Either ClientError r
_ = Bool
False

code :: ResponseF a -> Int
code :: forall a. ResponseF a -> Int
code = Status -> Int
statusCode (Status -> Int) -> (ResponseF a -> Status) -> ResponseF a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ResponseF a -> Status
forall a. ResponseF a -> Status
responseStatusCode

shouldRetryClientError :: ClientError -> Bool
shouldRetryClientError :: ClientError -> Bool
shouldRetryClientError (ClientError.FailureResponse RequestF () (BaseUrl, ByteString)
_ Response
resp) | Response -> Int
forall a. ResponseF a -> Int
code Response
resp Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
501 = Bool
False -- 501 Not Implemented
shouldRetryClientError (ClientError.FailureResponse RequestF () (BaseUrl, ByteString)
_ Response
resp) | Response -> Int
forall a. ResponseF a -> Int
code Response
resp Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
505 = Bool
False -- 505 HTTP Version Not Supported
shouldRetryClientError (ClientError.FailureResponse RequestF () (BaseUrl, ByteString)
_ Response
resp) | Response -> Int
forall a. ResponseF a -> Int
code Response
resp Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
408 = Bool
True -- 408 Request Timeout
shouldRetryClientError (ClientError.FailureResponse RequestF () (BaseUrl, ByteString)
_ Response
resp) | Response -> Int
forall a. ResponseF a -> Int
code Response
resp Int -> (Int, Int) -> Bool
forall a. Ord a => a -> (a, a) -> Bool
`inLowRange` (Int
500, Int
600) = Bool
True
shouldRetryClientError (ClientError.DecodeFailure Text
_ Response
_) = Bool
False -- Server programming error or API incompatibility
shouldRetryClientError (ClientError.UnsupportedContentType MediaType
_ Response
_) = Bool
False
shouldRetryClientError (ClientError.InvalidContentTypeHeader Response
_) = Bool
False
shouldRetryClientError (ClientError.ConnectionError SomeException
_) = Bool
True
shouldRetryClientError ClientError
_ = Bool
False

-- | ClientError printer that won't leak sensitive info.
clientErrorSummary :: ClientError -> Text
clientErrorSummary :: ClientError -> Text
clientErrorSummary (ClientError.FailureResponse RequestF () (BaseUrl, ByteString)
_ Response
resp) = Text
"status " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Status -> Text
forall a b. (Show a, ConvertText String b) => a -> b
show (Response -> Status
forall a. ResponseF a -> Status
responseStatusCode Response
resp)
clientErrorSummary ClientError.DecodeFailure {} = Text
"decode failure"
clientErrorSummary ClientError.UnsupportedContentType {} = Text
"unsupported content type"
clientErrorSummary ClientError.InvalidContentTypeHeader {} = Text
"invalid content type header"
clientErrorSummary (ClientError.ConnectionError SomeException
e) = Text
"connection error: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SomeException -> Text
forall a b. (Show a, ConvertText String b) => a -> b
show SomeException
e