{-# 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.VideoIntelligence.Videos.Annotate
(
VideoIntelligenceVideosAnnotateResource,
VideoIntelligenceVideosAnnotate (..),
newVideoIntelligenceVideosAnnotate,
)
where
import Gogol.Prelude qualified as Core
import Gogol.VideoIntelligence.Types
type VideoIntelligenceVideosAnnotateResource =
"v1p3beta1"
Core.:> "videos:annotate"
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]
GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
Core.:> Core.Post '[Core.JSON] GoogleLongrunning_Operation
data VideoIntelligenceVideosAnnotate = VideoIntelligenceVideosAnnotate
{
VideoIntelligenceVideosAnnotate -> Maybe Xgafv
xgafv :: (Core.Maybe Xgafv),
VideoIntelligenceVideosAnnotate -> Maybe Text
accessToken :: (Core.Maybe Core.Text),
VideoIntelligenceVideosAnnotate -> Maybe Text
callback :: (Core.Maybe Core.Text),
VideoIntelligenceVideosAnnotate
-> GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
payload :: GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest,
VideoIntelligenceVideosAnnotate -> Maybe Text
uploadType :: (Core.Maybe Core.Text),
VideoIntelligenceVideosAnnotate -> Maybe Text
uploadProtocol :: (Core.Maybe Core.Text)
}
deriving (VideoIntelligenceVideosAnnotate
-> VideoIntelligenceVideosAnnotate -> Bool
(VideoIntelligenceVideosAnnotate
-> VideoIntelligenceVideosAnnotate -> Bool)
-> (VideoIntelligenceVideosAnnotate
-> VideoIntelligenceVideosAnnotate -> Bool)
-> Eq VideoIntelligenceVideosAnnotate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VideoIntelligenceVideosAnnotate
-> VideoIntelligenceVideosAnnotate -> Bool
== :: VideoIntelligenceVideosAnnotate
-> VideoIntelligenceVideosAnnotate -> Bool
$c/= :: VideoIntelligenceVideosAnnotate
-> VideoIntelligenceVideosAnnotate -> Bool
/= :: VideoIntelligenceVideosAnnotate
-> VideoIntelligenceVideosAnnotate -> Bool
Core.Eq, Int -> VideoIntelligenceVideosAnnotate -> ShowS
[VideoIntelligenceVideosAnnotate] -> ShowS
VideoIntelligenceVideosAnnotate -> String
(Int -> VideoIntelligenceVideosAnnotate -> ShowS)
-> (VideoIntelligenceVideosAnnotate -> String)
-> ([VideoIntelligenceVideosAnnotate] -> ShowS)
-> Show VideoIntelligenceVideosAnnotate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VideoIntelligenceVideosAnnotate -> ShowS
showsPrec :: Int -> VideoIntelligenceVideosAnnotate -> ShowS
$cshow :: VideoIntelligenceVideosAnnotate -> String
show :: VideoIntelligenceVideosAnnotate -> String
$cshowList :: [VideoIntelligenceVideosAnnotate] -> ShowS
showList :: [VideoIntelligenceVideosAnnotate] -> ShowS
Core.Show, (forall x.
VideoIntelligenceVideosAnnotate
-> Rep VideoIntelligenceVideosAnnotate x)
-> (forall x.
Rep VideoIntelligenceVideosAnnotate x
-> VideoIntelligenceVideosAnnotate)
-> Generic VideoIntelligenceVideosAnnotate
forall x.
Rep VideoIntelligenceVideosAnnotate x
-> VideoIntelligenceVideosAnnotate
forall x.
VideoIntelligenceVideosAnnotate
-> Rep VideoIntelligenceVideosAnnotate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
VideoIntelligenceVideosAnnotate
-> Rep VideoIntelligenceVideosAnnotate x
from :: forall x.
VideoIntelligenceVideosAnnotate
-> Rep VideoIntelligenceVideosAnnotate x
$cto :: forall x.
Rep VideoIntelligenceVideosAnnotate x
-> VideoIntelligenceVideosAnnotate
to :: forall x.
Rep VideoIntelligenceVideosAnnotate x
-> VideoIntelligenceVideosAnnotate
Core.Generic)
newVideoIntelligenceVideosAnnotate ::
GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest ->
VideoIntelligenceVideosAnnotate
newVideoIntelligenceVideosAnnotate :: GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
-> VideoIntelligenceVideosAnnotate
newVideoIntelligenceVideosAnnotate GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
payload =
VideoIntelligenceVideosAnnotate
{ 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,
payload :: GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
payload = GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
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 VideoIntelligenceVideosAnnotate where
type
Rs VideoIntelligenceVideosAnnotate =
GoogleLongrunning_Operation
type
Scopes VideoIntelligenceVideosAnnotate =
'[CloudPlatform'FullControl]
requestClient :: VideoIntelligenceVideosAnnotate
-> GClient (Rs VideoIntelligenceVideosAnnotate)
requestClient VideoIntelligenceVideosAnnotate {Maybe Text
Maybe Xgafv
GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
xgafv :: VideoIntelligenceVideosAnnotate -> Maybe Xgafv
accessToken :: VideoIntelligenceVideosAnnotate -> Maybe Text
callback :: VideoIntelligenceVideosAnnotate -> Maybe Text
payload :: VideoIntelligenceVideosAnnotate
-> GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
uploadType :: VideoIntelligenceVideosAnnotate -> Maybe Text
uploadProtocol :: VideoIntelligenceVideosAnnotate -> Maybe Text
xgafv :: Maybe Xgafv
accessToken :: Maybe Text
callback :: Maybe Text
payload :: GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
uploadType :: Maybe Text
uploadProtocol :: Maybe Text
..} =
Maybe Xgafv
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe AltJSON
-> GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
-> ServiceConfig
-> GClient GoogleLongrunning_Operation
go
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)
GoogleCloudVideointelligenceV1p3beta1_AnnotateVideoRequest
payload
ServiceConfig
videoIntelligenceService
where
go :: Fn VideoIntelligenceVideosAnnotateResource
go =
Proxy VideoIntelligenceVideosAnnotateResource
-> Request -> Fn VideoIntelligenceVideosAnnotateResource
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
Core.buildClient
(Proxy VideoIntelligenceVideosAnnotateResource
forall {k} (t :: k). Proxy t
Core.Proxy :: Core.Proxy VideoIntelligenceVideosAnnotateResource)
Request
forall a. Monoid a => a
Core.mempty