{-# 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.Vault.Operations.List
(
VaultOperationsListResource,
VaultOperationsList (..),
newVaultOperationsList,
)
where
import Gogol.Prelude qualified as Core
import Gogol.Vault.Types
type VaultOperationsListResource =
"v1"
Core.:> Core.Capture "name" Core.Text
Core.:> Core.QueryParam "$.xgafv" Xgafv
Core.:> Core.QueryParam "access_token" Core.Text
Core.:> Core.QueryParam "callback" Core.Text
Core.:> Core.QueryParam "filter" Core.Text
Core.:> Core.QueryParam "pageSize" Core.Int32
Core.:> Core.QueryParam "pageToken" Core.Text
Core.:> Core.QueryParam "uploadType" Core.Text
Core.:> Core.QueryParam "upload_protocol" Core.Text
Core.:> Core.QueryParam "alt" Core.AltJSON
Core.:> Core.Get '[Core.JSON] ListOperationsResponse
data VaultOperationsList = VaultOperationsList
{
VaultOperationsList -> Maybe Xgafv
xgafv :: (Core.Maybe Xgafv),
VaultOperationsList -> Maybe Text
accessToken :: (Core.Maybe Core.Text),
VaultOperationsList -> Maybe Text
callback :: (Core.Maybe Core.Text),
VaultOperationsList -> Maybe Text
filter :: (Core.Maybe Core.Text),
VaultOperationsList -> Text
name :: Core.Text,
VaultOperationsList -> Maybe Int32
pageSize :: (Core.Maybe Core.Int32),
VaultOperationsList -> Maybe Text
pageToken :: (Core.Maybe Core.Text),
VaultOperationsList -> Maybe Text
uploadType :: (Core.Maybe Core.Text),
VaultOperationsList -> Maybe Text
uploadProtocol :: (Core.Maybe Core.Text)
}
deriving (VaultOperationsList -> VaultOperationsList -> Bool
(VaultOperationsList -> VaultOperationsList -> Bool)
-> (VaultOperationsList -> VaultOperationsList -> Bool)
-> Eq VaultOperationsList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VaultOperationsList -> VaultOperationsList -> Bool
== :: VaultOperationsList -> VaultOperationsList -> Bool
$c/= :: VaultOperationsList -> VaultOperationsList -> Bool
/= :: VaultOperationsList -> VaultOperationsList -> Bool
Core.Eq, Int -> VaultOperationsList -> ShowS
[VaultOperationsList] -> ShowS
VaultOperationsList -> String
(Int -> VaultOperationsList -> ShowS)
-> (VaultOperationsList -> String)
-> ([VaultOperationsList] -> ShowS)
-> Show VaultOperationsList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VaultOperationsList -> ShowS
showsPrec :: Int -> VaultOperationsList -> ShowS
$cshow :: VaultOperationsList -> String
show :: VaultOperationsList -> String
$cshowList :: [VaultOperationsList] -> ShowS
showList :: [VaultOperationsList] -> ShowS
Core.Show, (forall x. VaultOperationsList -> Rep VaultOperationsList x)
-> (forall x. Rep VaultOperationsList x -> VaultOperationsList)
-> Generic VaultOperationsList
forall x. Rep VaultOperationsList x -> VaultOperationsList
forall x. VaultOperationsList -> Rep VaultOperationsList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VaultOperationsList -> Rep VaultOperationsList x
from :: forall x. VaultOperationsList -> Rep VaultOperationsList x
$cto :: forall x. Rep VaultOperationsList x -> VaultOperationsList
to :: forall x. Rep VaultOperationsList x -> VaultOperationsList
Core.Generic)
newVaultOperationsList ::
Core.Text ->
VaultOperationsList
newVaultOperationsList :: Text -> VaultOperationsList
newVaultOperationsList Text
name =
VaultOperationsList
{ 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,
filter :: Maybe Text
filter = Maybe Text
forall a. Maybe a
Core.Nothing,
name :: Text
name = Text
name,
pageSize :: Maybe Int32
pageSize = Maybe Int32
forall a. Maybe a
Core.Nothing,
pageToken :: Maybe Text
pageToken = Maybe Text
forall a. Maybe a
Core.Nothing,
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 VaultOperationsList where
type Rs VaultOperationsList = ListOperationsResponse
type
Scopes VaultOperationsList =
'[Ediscovery'FullControl, Ediscovery'Readonly]
requestClient :: VaultOperationsList -> GClient (Rs VaultOperationsList)
requestClient VaultOperationsList {Maybe Int32
Maybe Text
Maybe Xgafv
Text
xgafv :: VaultOperationsList -> Maybe Xgafv
accessToken :: VaultOperationsList -> Maybe Text
callback :: VaultOperationsList -> Maybe Text
filter :: VaultOperationsList -> Maybe Text
name :: VaultOperationsList -> Text
pageSize :: VaultOperationsList -> Maybe Int32
pageToken :: VaultOperationsList -> Maybe Text
uploadType :: VaultOperationsList -> Maybe Text
uploadProtocol :: VaultOperationsList -> Maybe Text
xgafv :: Maybe Xgafv
accessToken :: Maybe Text
callback :: Maybe Text
filter :: Maybe Text
name :: Text
pageSize :: Maybe Int32
pageToken :: Maybe Text
uploadType :: Maybe Text
uploadProtocol :: Maybe Text
..} =
Text
-> Maybe Xgafv
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int32
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe AltJSON
-> ServiceConfig
-> GClient ListOperationsResponse
go
Text
name
Maybe Xgafv
xgafv
Maybe Text
accessToken
Maybe Text
callback
Maybe Text
filter
Maybe Int32
pageSize
Maybe Text
pageToken
Maybe Text
uploadType
Maybe Text
uploadProtocol
(AltJSON -> Maybe AltJSON
forall a. a -> Maybe a
Core.Just AltJSON
Core.AltJSON)
ServiceConfig
vaultService
where
go :: Fn VaultOperationsListResource
go =
Proxy VaultOperationsListResource
-> Request -> Fn VaultOperationsListResource
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
Core.buildClient
(Proxy VaultOperationsListResource
forall {k} (t :: k). Proxy t
Core.Proxy :: Core.Proxy VaultOperationsListResource)
Request
forall a. Monoid a => a
Core.mempty