{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- |
-- Module      : Gogol.Vision.Projects.Locations.Images.AsyncBatchAnnotate
-- Copyright   : (c) 2015-2025 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay <brendan.g.hay+gogol@gmail.com>
--               Toni Cebrián <toni@tonicebrian.com>
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Run asynchronous image detection and annotation for a list of images. Progress and results can be retrieved through the @google.longrunning.Operations@ interface. @Operation.metadata@ contains @OperationMetadata@ (metadata). @Operation.response@ contains @AsyncBatchAnnotateImagesResponse@ (results). This service will write image annotation outputs to json files in customer GCS bucket, each json file containing BatchAnnotateImagesResponse proto.
--
-- /See:/ <https://cloud.google.com/vision/ Cloud Vision API Reference> for @vision.projects.locations.images.asyncBatchAnnotate@.
module Gogol.Vision.Projects.Locations.Images.AsyncBatchAnnotate
  ( -- * Resource
    VisionProjectsLocationsImagesAsyncBatchAnnotateResource,

    -- ** Constructing a Request
    VisionProjectsLocationsImagesAsyncBatchAnnotate (..),
    newVisionProjectsLocationsImagesAsyncBatchAnnotate,
  )
where

import Gogol.Prelude qualified as Core
import Gogol.Vision.Types

-- | A resource alias for @vision.projects.locations.images.asyncBatchAnnotate@ method which the
-- 'VisionProjectsLocationsImagesAsyncBatchAnnotate' request conforms to.
type VisionProjectsLocationsImagesAsyncBatchAnnotateResource =
  "v1p2beta1"
    Core.:> Core.Capture "parent" Core.Text
    Core.:> "images:asyncBatchAnnotate"
    Core.:> Core.QueryParam "$.xgafv" Xgafv
    Core.:> Core.QueryParam "access_token" Core.Text
    Core.:> Core.QueryParam "callback" Core.Text
    Core.:> Core.QueryParam "uploadType" Core.Text
    Core.:> Core.QueryParam "upload_protocol" Core.Text
    Core.:> Core.QueryParam "alt" Core.AltJSON
    Core.:> Core.ReqBody
              '[Core.JSON]
              GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
    Core.:> Core.Post '[Core.JSON] Operation

-- | Run asynchronous image detection and annotation for a list of images. Progress and results can be retrieved through the @google.longrunning.Operations@ interface. @Operation.metadata@ contains @OperationMetadata@ (metadata). @Operation.response@ contains @AsyncBatchAnnotateImagesResponse@ (results). This service will write image annotation outputs to json files in customer GCS bucket, each json file containing BatchAnnotateImagesResponse proto.
--
-- /See:/ 'newVisionProjectsLocationsImagesAsyncBatchAnnotate' smart constructor.
data VisionProjectsLocationsImagesAsyncBatchAnnotate = VisionProjectsLocationsImagesAsyncBatchAnnotate
  { -- | V1 error format.
    VisionProjectsLocationsImagesAsyncBatchAnnotate -> Maybe Xgafv
xgafv :: (Core.Maybe Xgafv),
    -- | OAuth access token.
    VisionProjectsLocationsImagesAsyncBatchAnnotate -> Maybe Text
accessToken :: (Core.Maybe Core.Text),
    -- | JSONP
    VisionProjectsLocationsImagesAsyncBatchAnnotate -> Maybe Text
callback :: (Core.Maybe Core.Text),
    -- | Optional. Target project and location to make a call. Format: @projects\/{project-id}\/locations\/{location-id}@. If no parent is specified, a region will be chosen automatically. Supported location-ids: @us@: USA country only, @asia@: East asia areas, like Japan, Taiwan, @eu@: The European Union. Example: @projects\/project-A\/locations\/eu@.
    VisionProjectsLocationsImagesAsyncBatchAnnotate -> Text
parent :: Core.Text,
    -- | Multipart request metadata.
    VisionProjectsLocationsImagesAsyncBatchAnnotate
-> GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
payload :: GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest,
    -- | Legacy upload protocol for media (e.g. \"media\", \"multipart\").
    VisionProjectsLocationsImagesAsyncBatchAnnotate -> Maybe Text
uploadType :: (Core.Maybe Core.Text),
    -- | Upload protocol for media (e.g. \"raw\", \"multipart\").
    VisionProjectsLocationsImagesAsyncBatchAnnotate -> Maybe Text
uploadProtocol :: (Core.Maybe Core.Text)
  }
  deriving (VisionProjectsLocationsImagesAsyncBatchAnnotate
-> VisionProjectsLocationsImagesAsyncBatchAnnotate -> Bool
(VisionProjectsLocationsImagesAsyncBatchAnnotate
 -> VisionProjectsLocationsImagesAsyncBatchAnnotate -> Bool)
-> (VisionProjectsLocationsImagesAsyncBatchAnnotate
    -> VisionProjectsLocationsImagesAsyncBatchAnnotate -> Bool)
-> Eq VisionProjectsLocationsImagesAsyncBatchAnnotate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VisionProjectsLocationsImagesAsyncBatchAnnotate
-> VisionProjectsLocationsImagesAsyncBatchAnnotate -> Bool
== :: VisionProjectsLocationsImagesAsyncBatchAnnotate
-> VisionProjectsLocationsImagesAsyncBatchAnnotate -> Bool
$c/= :: VisionProjectsLocationsImagesAsyncBatchAnnotate
-> VisionProjectsLocationsImagesAsyncBatchAnnotate -> Bool
/= :: VisionProjectsLocationsImagesAsyncBatchAnnotate
-> VisionProjectsLocationsImagesAsyncBatchAnnotate -> Bool
Core.Eq, Int -> VisionProjectsLocationsImagesAsyncBatchAnnotate -> ShowS
[VisionProjectsLocationsImagesAsyncBatchAnnotate] -> ShowS
VisionProjectsLocationsImagesAsyncBatchAnnotate -> String
(Int -> VisionProjectsLocationsImagesAsyncBatchAnnotate -> ShowS)
-> (VisionProjectsLocationsImagesAsyncBatchAnnotate -> String)
-> ([VisionProjectsLocationsImagesAsyncBatchAnnotate] -> ShowS)
-> Show VisionProjectsLocationsImagesAsyncBatchAnnotate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VisionProjectsLocationsImagesAsyncBatchAnnotate -> ShowS
showsPrec :: Int -> VisionProjectsLocationsImagesAsyncBatchAnnotate -> ShowS
$cshow :: VisionProjectsLocationsImagesAsyncBatchAnnotate -> String
show :: VisionProjectsLocationsImagesAsyncBatchAnnotate -> String
$cshowList :: [VisionProjectsLocationsImagesAsyncBatchAnnotate] -> ShowS
showList :: [VisionProjectsLocationsImagesAsyncBatchAnnotate] -> ShowS
Core.Show, (forall x.
 VisionProjectsLocationsImagesAsyncBatchAnnotate
 -> Rep VisionProjectsLocationsImagesAsyncBatchAnnotate x)
-> (forall x.
    Rep VisionProjectsLocationsImagesAsyncBatchAnnotate x
    -> VisionProjectsLocationsImagesAsyncBatchAnnotate)
-> Generic VisionProjectsLocationsImagesAsyncBatchAnnotate
forall x.
Rep VisionProjectsLocationsImagesAsyncBatchAnnotate x
-> VisionProjectsLocationsImagesAsyncBatchAnnotate
forall x.
VisionProjectsLocationsImagesAsyncBatchAnnotate
-> Rep VisionProjectsLocationsImagesAsyncBatchAnnotate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
VisionProjectsLocationsImagesAsyncBatchAnnotate
-> Rep VisionProjectsLocationsImagesAsyncBatchAnnotate x
from :: forall x.
VisionProjectsLocationsImagesAsyncBatchAnnotate
-> Rep VisionProjectsLocationsImagesAsyncBatchAnnotate x
$cto :: forall x.
Rep VisionProjectsLocationsImagesAsyncBatchAnnotate x
-> VisionProjectsLocationsImagesAsyncBatchAnnotate
to :: forall x.
Rep VisionProjectsLocationsImagesAsyncBatchAnnotate x
-> VisionProjectsLocationsImagesAsyncBatchAnnotate
Core.Generic)

-- | Creates a value of 'VisionProjectsLocationsImagesAsyncBatchAnnotate' with the minimum fields required to make a request.
newVisionProjectsLocationsImagesAsyncBatchAnnotate ::
  -- |  Optional. Target project and location to make a call. Format: @projects\/{project-id}\/locations\/{location-id}@. If no parent is specified, a region will be chosen automatically. Supported location-ids: @us@: USA country only, @asia@: East asia areas, like Japan, Taiwan, @eu@: The European Union. Example: @projects\/project-A\/locations\/eu@. See 'parent'.
  Core.Text ->
  -- |  Multipart request metadata. See 'payload'.
  GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest ->
  VisionProjectsLocationsImagesAsyncBatchAnnotate
newVisionProjectsLocationsImagesAsyncBatchAnnotate :: Text
-> GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
-> VisionProjectsLocationsImagesAsyncBatchAnnotate
newVisionProjectsLocationsImagesAsyncBatchAnnotate Text
parent GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
payload =
  VisionProjectsLocationsImagesAsyncBatchAnnotate
    { xgafv :: Maybe Xgafv
xgafv =
        Maybe Xgafv
forall a. Maybe a
Core.Nothing,
      accessToken :: Maybe Text
accessToken = Maybe Text
forall a. Maybe a
Core.Nothing,
      callback :: Maybe Text
callback = Maybe Text
forall a. Maybe a
Core.Nothing,
      parent :: Text
parent = Text
parent,
      payload :: GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
payload = GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
payload,
      uploadType :: Maybe Text
uploadType = Maybe Text
forall a. Maybe a
Core.Nothing,
      uploadProtocol :: Maybe Text
uploadProtocol = Maybe Text
forall a. Maybe a
Core.Nothing
    }

instance
  Core.GoogleRequest
    VisionProjectsLocationsImagesAsyncBatchAnnotate
  where
  type Rs VisionProjectsLocationsImagesAsyncBatchAnnotate = Operation
  type
    Scopes VisionProjectsLocationsImagesAsyncBatchAnnotate =
      '[CloudPlatform'FullControl, CloudVision'FullControl]
  requestClient :: VisionProjectsLocationsImagesAsyncBatchAnnotate
-> GClient (Rs VisionProjectsLocationsImagesAsyncBatchAnnotate)
requestClient VisionProjectsLocationsImagesAsyncBatchAnnotate {Maybe Text
Maybe Xgafv
Text
GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
xgafv :: VisionProjectsLocationsImagesAsyncBatchAnnotate -> Maybe Xgafv
accessToken :: VisionProjectsLocationsImagesAsyncBatchAnnotate -> Maybe Text
callback :: VisionProjectsLocationsImagesAsyncBatchAnnotate -> Maybe Text
parent :: VisionProjectsLocationsImagesAsyncBatchAnnotate -> Text
payload :: VisionProjectsLocationsImagesAsyncBatchAnnotate
-> GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
uploadType :: VisionProjectsLocationsImagesAsyncBatchAnnotate -> Maybe Text
uploadProtocol :: VisionProjectsLocationsImagesAsyncBatchAnnotate -> Maybe Text
xgafv :: Maybe Xgafv
accessToken :: Maybe Text
callback :: Maybe Text
parent :: Text
payload :: GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
uploadType :: Maybe Text
uploadProtocol :: Maybe Text
..} =
    Text
-> Maybe Xgafv
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe AltJSON
-> GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
-> ServiceConfig
-> GClient Operation
go
      Text
parent
      Maybe Xgafv
xgafv
      Maybe Text
accessToken
      Maybe Text
callback
      Maybe Text
uploadType
      Maybe Text
uploadProtocol
      (AltJSON -> Maybe AltJSON
forall a. a -> Maybe a
Core.Just AltJSON
Core.AltJSON)
      GoogleCloudVisionV1p2beta1AsyncBatchAnnotateImagesRequest
payload
      ServiceConfig
visionService
    where
      go :: Fn VisionProjectsLocationsImagesAsyncBatchAnnotateResource
go =
        Proxy VisionProjectsLocationsImagesAsyncBatchAnnotateResource
-> Request
-> Fn VisionProjectsLocationsImagesAsyncBatchAnnotateResource
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
Core.buildClient
          ( Proxy VisionProjectsLocationsImagesAsyncBatchAnnotateResource
forall {k} (t :: k). Proxy t
Core.Proxy ::
              Core.Proxy VisionProjectsLocationsImagesAsyncBatchAnnotateResource
          )
          Request
forall a. Monoid a => a
Core.mempty