{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}

module Hercules.API.Projects where

import Hercules.API.Accounts.Account (Account)
import Hercules.API.Build.EvaluationDetail
  ( EvaluationDetail,
  )
import qualified Hercules.API.Build.FailureGraph as FailureGraph
import Hercules.API.Build.Log (Log)
import Hercules.API.Forge.Forge (Forge)
import Hercules.API.Inputs.ImmutableGitInput (ImmutableGitInput)
import Hercules.API.Paging (PagedResponse)
import Hercules.API.Prelude
import Hercules.API.Projects.CreateProject
  ( CreateProject,
  )
import Hercules.API.Projects.CreateUserEffectTokenResponse (CreateUserEffectTokenResponse)
import Hercules.API.Projects.Job
  ( Job,
    ProjectAndJobs,
  )
import Hercules.API.Projects.JobHandlers (JobHandlers)
import Hercules.API.Projects.PatchProject
  ( PatchProject,
  )
import Hercules.API.Projects.Project (Project)
import Servant.API

type GetJsonWithPreflight a =
  Get
    '[JSON]
    (Headers '[Header "Access-Control-Allow-Origin" Text] a)
    :<|> Verb
           'OPTIONS
           204
           '[JSON]
           ( Headers
               '[ Header "Access-Control-Allow-Origin" Text,
                  Header "Access-Control-Allow-Headers" Text,
                  Header "Access-Control-Allow-Methods" Text
                ]
               NoContent
           )

data ProjectResourceGroup auth f = ProjectResourceGroup
  { forall auth f.
ProjectResourceGroup auth f
-> f
   :- (Summary "Retrieve a project" :> (auth :> Get '[JSON] Project))
get ::
      f
        :- Summary "Retrieve a project"
          :> auth
          :> Get '[JSON] Project,
    forall auth f.
ProjectResourceGroup auth f
-> f
   :- (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)
                       :> (QueryParam'
                             '[Optional,
                               Description
                                 "Return jobs that come \"after\" the provided index in the response order."]
                             "offsetIndex"
                             Int64
                           :> (QueryParam'
                                 '[Optional, Description "Return at most n jobs."] "limit" Int64
                               :> (auth :> GetJsonWithPreflight PagedJobs))))))))
getJobs ::
      f
        :- 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)
          :> QueryParam' '[Optional, Description "Return jobs that come \"after\" the provided index in the response order."] "offsetIndex" Int64
          :> QueryParam' '[Optional, Description "Return at most n jobs."] "limit" Int64
          :> auth
          :> GetJsonWithPreflight PagedJobs,
    forall auth f.
ProjectResourceGroup auth f
-> f
   :- (Summary
         "Get source information from the latest successful job/jobs satisfying the provided requirements."
       :> (Description
             "The job parameter can be omitted to require all jobs for a commit to succeed. This can have the unexpected effect of reverting when a change in the extraInputs causes a regression. So it is recommended to specify one or more jobs. Common examples are \"onPush.default\" for a pinned build or \"onPush.ci\" for a build using extraInputs to integrate continuously."
           :> ("source"
               :> (QueryParam'
                     '[Optional,
                       Description
                         "Constrain the results by git ref, such as refs/heads/my-branch. Defaults to HEAD."]
                     "ref"
                     Text
                   :> (QueryParams "jobs" Text
                       :> (auth :> Get '[JSON] ImmutableGitInput))))))
getJobSource ::
      f
        :- Summary "Get source information from the latest successful job/jobs satisfying the provided requirements."
          :> Description "The job parameter can be omitted to require all jobs for a commit to succeed. This can have the unexpected effect of reverting when a change in the extraInputs causes a regression. So it is recommended to specify one or more jobs. Common examples are \"onPush.default\" for a pinned build or \"onPush.ci\" for a build using extraInputs to integrate continuously."
          :> "source"
          :> QueryParam' '[Optional, Description "Constrain the results by git ref, such as refs/heads/my-branch. Defaults to HEAD."] "ref" Text
          :> QueryParams "jobs" Text
          :> auth
          :> Get '[JSON] ImmutableGitInput
  }
  deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall auth f x.
Rep (ProjectResourceGroup auth f) x -> ProjectResourceGroup auth f
forall auth f x.
ProjectResourceGroup auth f -> Rep (ProjectResourceGroup auth f) x
$cto :: forall auth f x.
Rep (ProjectResourceGroup auth f) x -> ProjectResourceGroup auth f
$cfrom :: forall auth f x.
ProjectResourceGroup auth f -> Rep (ProjectResourceGroup auth f) x
Generic)

data ProjectsAPI auth f = ProjectsAPI
  { forall auth f.
ProjectsAPI auth f
-> f
   :- Substitute
        ("projects"
         :> (Capture' '[Required, Strict] "projectId" (Id Project)
             :> Placeholder))
        (ToServantApi (ProjectResourceGroup auth))
byProjectId ::
      f
        :- Substitute
             ( "projects"
                 :> Capture' '[Required, Strict] "projectId" (Id Project)
                 :> Placeholder
             )
             (ToServantApi (ProjectResourceGroup auth)),
    forall auth f.
ProjectsAPI auth f
-> f
   :- Substitute
        ("site"
         :> (Capture' '[Required, Strict] "site" (Name Forge)
             :> ("account"
                 :> (Capture' '[Required, Strict] "account" (Name Account)
                     :> ("project"
                         :> (Capture' '[Required, Strict] "project" (Name Project)
                             :> Placeholder))))))
        (ToServantApi (ProjectResourceGroup auth))
byProjectName ::
      f
        :- Substitute
             ( "site"
                 :> Capture' '[Required, Strict] "site" (Name Forge)
                 :> "account"
                 :> Capture' '[Required, Strict] "account" (Name Account)
                 :> "project"
                 :> Capture' '[Required, Strict] "project" (Name Project)
                 :> Placeholder
             )
             (ToServantApi (ProjectResourceGroup auth)),
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "List all projects owned by an account."
       :> ("accounts"
           :> (Capture' '[Required, Strict] "accountId" (Id Account)
               :> ("projects" :> (auth :> Get '[JSON] [Project])))))
projectsByOwner ::
      f
        :- Summary "List all projects owned by an account."
          :> "accounts"
          :> Capture' '[Required, Strict] "accountId" (Id Account)
          :> "projects"
          :> auth
          :> Get '[JSON] [Project],
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "Find projects"
       :> ("projects"
           :> (QueryParam' '[Optional] "site" (Name Forge)
               :> (QueryParam' '[Optional] "account" (Name Account)
                   :> (QueryParam' '[Optional] "project" (Name Project)
                       :> (auth :> Get '[JSON] [Project]))))))
findProjects ::
      f
        :- Summary "Find projects"
          :> "projects"
          :> QueryParam' '[Optional] "site" (Name Forge)
          :> QueryParam' '[Optional] "account" (Name Account)
          :> QueryParam' '[Optional] "project" (Name Project)
          :> auth
          :> Get '[JSON] [Project],
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "Create a new project."
       :> ("projects"
           :> (auth
               :> (ReqBody '[JSON] CreateProject :> Post '[JSON] (Id Project)))))
createProject ::
      f
        :- Summary "Create a new project."
          :> "projects"
          :> auth
          :> ReqBody '[JSON] CreateProject
          :> Post '[JSON] (Id Project),
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "Modify a project"
       :> ("projects"
           :> (Capture' '[Required, Strict] "projectId" (Id Project)
               :> (ReqBody '[JSON] PatchProject
                   :> (auth :> Patch '[JSON] Project)))))
patchProject ::
      f
        :- Summary "Modify a project"
          :> "projects"
          :> Capture' '[Required, Strict] "projectId" (Id Project)
          :> ReqBody '[JSON] PatchProject
          :> auth
          :> Patch '[JSON] Project,
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "Create a token for local effect execution"
       :> ("projects"
           :> (Capture' '[Required, Strict] "projectId" (Id Project)
               :> (auth
                   :> ("create-user-effect-token"
                       :> Post '[JSON] CreateUserEffectTokenResponse)))))
createUserEffectToken ::
      f
        :- Summary "Create a token for local effect execution"
          :> "projects"
          :> Capture' '[Required, Strict] "projectId" (Id Project)
          :> auth
          :> "create-user-effect-token"
          :> Post '[JSON] CreateUserEffectTokenResponse,
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "Find jobs"
       :> ("jobs"
           :> (QueryParam'
                 '[Optional,
                   Description "Currently only \"github\" or omit entirely"]
                 "site"
                 (Name Forge)
               :> (QueryParam'
                     '[Optional, Description "Account name filter"]
                     "account"
                     (Name Account)
                   :> (QueryParam'
                         '[Optional,
                           Description
                             "Project name filter. Required if you want to retrieve all jobs"]
                         "project"
                         (Name Project)
                       :> (QueryParam'
                             '[Optional, Description "To get a specific job by index"]
                             "index"
                             Int
                           :> (QueryParam'
                                 '[Optional,
                                   Description
                                     "Number of latest jobs to get, when project name is omitted. Range [1..50], default 10."]
                                 "latest"
                                 Int
                               :> (auth :> Get '[JSON] [ProjectAndJobs]))))))))
findJobs ::
      f
        :- Summary "Find jobs"
          :> "jobs"
          :> QueryParam' '[Optional, Description "Currently only \"github\" or omit entirely"] "site" (Name Forge)
          :> QueryParam' '[Optional, Description "Account name filter"] "account" (Name Account)
          :> QueryParam' '[Optional, Description "Project name filter. Required if you want to retrieve all jobs"] "project" (Name Project)
          :> QueryParam' '[Optional, Description "To get a specific job by index"] "index" Int
          :> QueryParam' '[Optional, Description "Number of latest jobs to get, when project name is omitted. Range [1..50], default 10."] "latest" Int
          :> auth
          :> Get '[JSON] [ProjectAndJobs],
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "Get a job's handler declarations, if any."
       :> (Description
             "Handlers define what to build and do on events such as onPush, onSchedule."
           :> ("jobs"
               :> (Capture' '[Required, Strict] "jobId" (Id Job)
                   :> ("handlers" :> (auth :> Get '[JSON] JobHandlers))))))
getJobHandlers ::
      f
        :- Summary "Get a job's handler declarations, if any."
          :> Description "Handlers define what to build and do on events such as onPush, onSchedule."
          :> "jobs"
          :> Capture' '[Required, Strict] "jobId" (Id Job)
          :> "handlers"
          :> auth
          :> Get '[JSON] JobHandlers,
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "List all attributes in a job"
       :> (Description
             "A list of all attributes that have been produced as part of the evaluation of a job."
           :> ("jobs"
               :> (Capture' '[Required, Strict] "jobId" (Id Job)
                   :> ("evaluation"
                       :> (auth :> GetJsonWithPreflight EvaluationDetail))))))
projectJobEvaluation ::
      f
        :- Summary "List all attributes in a job"
          :> Description "A list of all attributes that have been produced as part of the evaluation of a job."
          :> "jobs"
          :> Capture' '[Required, Strict] "jobId" (Id Job)
          :> "evaluation"
          :> auth
          :> GetJsonWithPreflight EvaluationDetail,
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "Find all failures in an evaluation's derivations"
       :> (Description
             "Returns all derivations that have failures in their dependency closures."
           :> ("jobs"
               :> (Capture' '[Required, Strict] "jobId" (Id Job)
                   :> ("derivations" :> ("failed" :> (auth :> Get '[JSON] Graph)))))))
jobDerivationFailureGraph ::
      f
        :- Summary "Find all failures in an evaluation's derivations"
          :> Description
               "Returns all derivations that have failures in their dependency closures."
          :> "jobs"
          :> Capture' '[Required, Strict] "jobId" (Id Job)
          :> "derivations"
          :> "failed"
          :> auth
          :> Get '[JSON] FailureGraph.Graph,
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "Create a new job like this job"
       :> (Description
             "The newly created job will be in the same project, have the same inputs but a new evaluation. The response has the newly created job."
           :> ("jobs"
               :> (Capture' '[Required, Strict] "jobId" (Id Job)
                   :> ("rerun"
                       :> (QueryParam "rebuildFailures" Bool
                           :> (auth :> Post '[JSON] Job)))))))
jobRerun ::
      f
        :- Summary "Create a new job like this job"
          :> Description
               "The newly created job will be in the same project, have the same inputs but a new evaluation.\
               \ The response has the newly created job."
          :> "jobs"
          :> Capture' '[Required, Strict] "jobId" (Id Job)
          :> "rerun"
          :> QueryParam "rebuildFailures" Bool
          :> auth
          :> Post '[JSON] Job,
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary
         "Create a scheduled job to run now, based on a configuration job."
       :> (Description
             "This is mostly intended for trying out new scheduled jobs before they are merged. The job is run in the context of the job's branch; not that of the default branch."
           :> ("jobs"
               :> (Capture' '[Required, Strict] "jobId" (Id Job)
                   :> ("on-schedule"
                       :> (Capture' '[Required, Strict] "jobName" Text
                           :> ("run" :> (auth :> Post '[JSON] Job))))))))
jobTriggerOnSchedule ::
      f
        :- Summary "Create a scheduled job to run now, based on a configuration job."
          :> Description
               "This is mostly intended for trying out new scheduled jobs before they are merged. The job is run in the context of the job's branch; not that of the default branch."
          :> "jobs"
          :> Capture' '[Required, Strict] "jobId" (Id Job)
          :> "on-schedule"
          :> Capture' '[Required, Strict] "jobName" Text
          :> "run"
          :> auth
          :> Post '[JSON] Job,
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "Cancel the job and any work that becomes redundant"
       :> (Description
             "Some derivations may keep going, if referenced by active jobs."
           :> ("jobs"
               :> (Capture' '[Required, Strict] "jobId" (Id Job)
                   :> ("cancel" :> (auth :> Post '[JSON] NoContent))))))
jobCancel ::
      f
        :- Summary "Cancel the job and any work that becomes redundant"
          :> Description
               "Some derivations may keep going, if referenced by active jobs."
          :> "jobs"
          :> Capture' '[Required, Strict] "jobId" (Id Job)
          :> "cancel"
          :> auth
          :> Post '[JSON] NoContent,
    forall auth f.
ProjectsAPI auth f
-> f
   :- (Summary "Read all recorded evaluation log entries"
       :> ("jobs"
           :> (Capture' '[Required, Strict] "jobId" (Id Job)
               :> ("evaluation"
                   :> ("log"
                       :> ("lines"
                           :> (QueryParam' '[Required] "logId" (Id "log")
                               :> (QueryParam' '[Optional] "iMin" Int
                                   :> (auth :> Get '[JSON] Log)))))))))
getEvaluationLog ::
      f
        :- Summary "Read all recorded evaluation log entries"
          :> "jobs"
          :> Capture' '[Required, Strict] "jobId" (Id Job)
          :> "evaluation"
          :> "log"
          :> "lines"
          :> QueryParam' '[Required] "logId" (Id "log")
          :> QueryParam' '[Optional] "iMin" Int
          :> auth
          :> Get '[JSON] Log
  }
  deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall auth f x. Rep (ProjectsAPI auth f) x -> ProjectsAPI auth f
forall auth f x. ProjectsAPI auth f -> Rep (ProjectsAPI auth f) x
$cto :: forall auth f x. Rep (ProjectsAPI auth f) x -> ProjectsAPI auth f
$cfrom :: forall auth f x. ProjectsAPI auth f -> Rep (ProjectsAPI auth f) x
Generic)

newtype PagedJobs = PagedJobs (PagedResponse Job)
  deriving (forall x. Rep PagedJobs x -> PagedJobs
forall x. PagedJobs -> Rep PagedJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PagedJobs x -> PagedJobs
$cfrom :: forall x. PagedJobs -> Rep PagedJobs x
Generic, Int -> PagedJobs -> ShowS
[PagedJobs] -> ShowS
PagedJobs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PagedJobs] -> ShowS
$cshowList :: [PagedJobs] -> ShowS
show :: PagedJobs -> String
$cshow :: PagedJobs -> String
showsPrec :: Int -> PagedJobs -> ShowS
$cshowsPrec :: Int -> PagedJobs -> ShowS
Show, PagedJobs -> PagedJobs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PagedJobs -> PagedJobs -> Bool
$c/= :: PagedJobs -> PagedJobs -> Bool
== :: PagedJobs -> PagedJobs -> Bool
$c== :: PagedJobs -> PagedJobs -> Bool
Eq, PagedJobs -> ()
forall a. (a -> ()) -> NFData a
rnf :: PagedJobs -> ()
$crnf :: PagedJobs -> ()
NFData, [PagedJobs] -> Encoding
[PagedJobs] -> Value
PagedJobs -> Encoding
PagedJobs -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PagedJobs] -> Encoding
$ctoEncodingList :: [PagedJobs] -> Encoding
toJSONList :: [PagedJobs] -> Value
$ctoJSONList :: [PagedJobs] -> Value
toEncoding :: PagedJobs -> Encoding
$ctoEncoding :: PagedJobs -> Encoding
toJSON :: PagedJobs -> Value
$ctoJSON :: PagedJobs -> Value
ToJSON, Value -> Parser [PagedJobs]
Value -> Parser PagedJobs
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PagedJobs]
$cparseJSONList :: Value -> Parser [PagedJobs]
parseJSON :: Value -> Parser PagedJobs
$cparseJSON :: Value -> Parser PagedJobs
FromJSON, Proxy PagedJobs -> Declare (Definitions Schema) NamedSchema
forall a.
(Proxy a -> Declare (Definitions Schema) NamedSchema) -> ToSchema a
declareNamedSchema :: Proxy PagedJobs -> Declare (Definitions Schema) NamedSchema
$cdeclareNamedSchema :: Proxy PagedJobs -> Declare (Definitions Schema) NamedSchema
ToSchema)