{-# 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.Files.AsyncBatchAnnotate
(
VisionProjectsFilesAsyncBatchAnnotateResource,
VisionProjectsFilesAsyncBatchAnnotate (..),
newVisionProjectsFilesAsyncBatchAnnotate,
)
where
import Gogol.Prelude qualified as Core
import Gogol.Vision.Types
type VisionProjectsFilesAsyncBatchAnnotateResource =
"v1p2beta1"
Core.:> Core.Capture "parent" Core.Text
Core.:> "files: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]
GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
Core.:> Core.Post '[Core.JSON] Operation
data VisionProjectsFilesAsyncBatchAnnotate = VisionProjectsFilesAsyncBatchAnnotate
{
VisionProjectsFilesAsyncBatchAnnotate -> Maybe Xgafv
xgafv :: (Core.Maybe Xgafv),
VisionProjectsFilesAsyncBatchAnnotate -> Maybe Text
accessToken :: (Core.Maybe Core.Text),
VisionProjectsFilesAsyncBatchAnnotate -> Maybe Text
callback :: (Core.Maybe Core.Text),
VisionProjectsFilesAsyncBatchAnnotate -> Text
parent :: Core.Text,
VisionProjectsFilesAsyncBatchAnnotate
-> GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
payload :: GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest,
VisionProjectsFilesAsyncBatchAnnotate -> Maybe Text
uploadType :: (Core.Maybe Core.Text),
VisionProjectsFilesAsyncBatchAnnotate -> Maybe Text
uploadProtocol :: (Core.Maybe Core.Text)
}
deriving (VisionProjectsFilesAsyncBatchAnnotate
-> VisionProjectsFilesAsyncBatchAnnotate -> Bool
(VisionProjectsFilesAsyncBatchAnnotate
-> VisionProjectsFilesAsyncBatchAnnotate -> Bool)
-> (VisionProjectsFilesAsyncBatchAnnotate
-> VisionProjectsFilesAsyncBatchAnnotate -> Bool)
-> Eq VisionProjectsFilesAsyncBatchAnnotate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VisionProjectsFilesAsyncBatchAnnotate
-> VisionProjectsFilesAsyncBatchAnnotate -> Bool
== :: VisionProjectsFilesAsyncBatchAnnotate
-> VisionProjectsFilesAsyncBatchAnnotate -> Bool
$c/= :: VisionProjectsFilesAsyncBatchAnnotate
-> VisionProjectsFilesAsyncBatchAnnotate -> Bool
/= :: VisionProjectsFilesAsyncBatchAnnotate
-> VisionProjectsFilesAsyncBatchAnnotate -> Bool
Core.Eq, Int -> VisionProjectsFilesAsyncBatchAnnotate -> ShowS
[VisionProjectsFilesAsyncBatchAnnotate] -> ShowS
VisionProjectsFilesAsyncBatchAnnotate -> String
(Int -> VisionProjectsFilesAsyncBatchAnnotate -> ShowS)
-> (VisionProjectsFilesAsyncBatchAnnotate -> String)
-> ([VisionProjectsFilesAsyncBatchAnnotate] -> ShowS)
-> Show VisionProjectsFilesAsyncBatchAnnotate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VisionProjectsFilesAsyncBatchAnnotate -> ShowS
showsPrec :: Int -> VisionProjectsFilesAsyncBatchAnnotate -> ShowS
$cshow :: VisionProjectsFilesAsyncBatchAnnotate -> String
show :: VisionProjectsFilesAsyncBatchAnnotate -> String
$cshowList :: [VisionProjectsFilesAsyncBatchAnnotate] -> ShowS
showList :: [VisionProjectsFilesAsyncBatchAnnotate] -> ShowS
Core.Show, (forall x.
VisionProjectsFilesAsyncBatchAnnotate
-> Rep VisionProjectsFilesAsyncBatchAnnotate x)
-> (forall x.
Rep VisionProjectsFilesAsyncBatchAnnotate x
-> VisionProjectsFilesAsyncBatchAnnotate)
-> Generic VisionProjectsFilesAsyncBatchAnnotate
forall x.
Rep VisionProjectsFilesAsyncBatchAnnotate x
-> VisionProjectsFilesAsyncBatchAnnotate
forall x.
VisionProjectsFilesAsyncBatchAnnotate
-> Rep VisionProjectsFilesAsyncBatchAnnotate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
VisionProjectsFilesAsyncBatchAnnotate
-> Rep VisionProjectsFilesAsyncBatchAnnotate x
from :: forall x.
VisionProjectsFilesAsyncBatchAnnotate
-> Rep VisionProjectsFilesAsyncBatchAnnotate x
$cto :: forall x.
Rep VisionProjectsFilesAsyncBatchAnnotate x
-> VisionProjectsFilesAsyncBatchAnnotate
to :: forall x.
Rep VisionProjectsFilesAsyncBatchAnnotate x
-> VisionProjectsFilesAsyncBatchAnnotate
Core.Generic)
newVisionProjectsFilesAsyncBatchAnnotate ::
Core.Text ->
GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest ->
VisionProjectsFilesAsyncBatchAnnotate
newVisionProjectsFilesAsyncBatchAnnotate :: Text
-> GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
-> VisionProjectsFilesAsyncBatchAnnotate
newVisionProjectsFilesAsyncBatchAnnotate Text
parent GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
payload =
VisionProjectsFilesAsyncBatchAnnotate
{ 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 :: GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
payload = GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
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 VisionProjectsFilesAsyncBatchAnnotate where
type Rs VisionProjectsFilesAsyncBatchAnnotate = Operation
type
Scopes VisionProjectsFilesAsyncBatchAnnotate =
'[CloudPlatform'FullControl, CloudVision'FullControl]
requestClient :: VisionProjectsFilesAsyncBatchAnnotate
-> GClient (Rs VisionProjectsFilesAsyncBatchAnnotate)
requestClient VisionProjectsFilesAsyncBatchAnnotate {Maybe Text
Maybe Xgafv
Text
GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
xgafv :: VisionProjectsFilesAsyncBatchAnnotate -> Maybe Xgafv
accessToken :: VisionProjectsFilesAsyncBatchAnnotate -> Maybe Text
callback :: VisionProjectsFilesAsyncBatchAnnotate -> Maybe Text
parent :: VisionProjectsFilesAsyncBatchAnnotate -> Text
payload :: VisionProjectsFilesAsyncBatchAnnotate
-> GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
uploadType :: VisionProjectsFilesAsyncBatchAnnotate -> Maybe Text
uploadProtocol :: VisionProjectsFilesAsyncBatchAnnotate -> Maybe Text
xgafv :: Maybe Xgafv
accessToken :: Maybe Text
callback :: Maybe Text
parent :: Text
payload :: GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
uploadType :: Maybe Text
uploadProtocol :: Maybe Text
..} =
Text
-> Maybe Xgafv
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe AltJSON
-> GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
-> 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)
GoogleCloudVisionV1p2beta1AsyncBatchAnnotateFilesRequest
payload
ServiceConfig
visionService
where
go :: Fn VisionProjectsFilesAsyncBatchAnnotateResource
go =
Proxy VisionProjectsFilesAsyncBatchAnnotateResource
-> Request -> Fn VisionProjectsFilesAsyncBatchAnnotateResource
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
Core.buildClient
( Proxy VisionProjectsFilesAsyncBatchAnnotateResource
forall {k} (t :: k). Proxy t
Core.Proxy ::
Core.Proxy VisionProjectsFilesAsyncBatchAnnotateResource
)
Request
forall a. Monoid a => a
Core.mempty