{-# 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.Matters.Holds.Get
(
VaultMattersHoldsGetResource,
VaultMattersHoldsGet (..),
newVaultMattersHoldsGet,
)
where
import Gogol.Prelude qualified as Core
import Gogol.Vault.Types
type VaultMattersHoldsGetResource =
"v1"
Core.:> "matters"
Core.:> Core.Capture "matterId" Core.Text
Core.:> "holds"
Core.:> Core.Capture "holdId" Core.Text
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 "view" MattersHoldsGetView
Core.:> Core.QueryParam "alt" Core.AltJSON
Core.:> Core.Get '[Core.JSON] Hold
data VaultMattersHoldsGet = VaultMattersHoldsGet
{
VaultMattersHoldsGet -> Maybe Xgafv
xgafv :: (Core.Maybe Xgafv),
VaultMattersHoldsGet -> Maybe Text
accessToken :: (Core.Maybe Core.Text),
VaultMattersHoldsGet -> Maybe Text
callback :: (Core.Maybe Core.Text),
VaultMattersHoldsGet -> Text
holdId :: Core.Text,
VaultMattersHoldsGet -> Text
matterId :: Core.Text,
VaultMattersHoldsGet -> Maybe Text
uploadType :: (Core.Maybe Core.Text),
VaultMattersHoldsGet -> Maybe Text
uploadProtocol :: (Core.Maybe Core.Text),
VaultMattersHoldsGet -> Maybe MattersHoldsGetView
view :: (Core.Maybe MattersHoldsGetView)
}
deriving (VaultMattersHoldsGet -> VaultMattersHoldsGet -> Bool
(VaultMattersHoldsGet -> VaultMattersHoldsGet -> Bool)
-> (VaultMattersHoldsGet -> VaultMattersHoldsGet -> Bool)
-> Eq VaultMattersHoldsGet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VaultMattersHoldsGet -> VaultMattersHoldsGet -> Bool
== :: VaultMattersHoldsGet -> VaultMattersHoldsGet -> Bool
$c/= :: VaultMattersHoldsGet -> VaultMattersHoldsGet -> Bool
/= :: VaultMattersHoldsGet -> VaultMattersHoldsGet -> Bool
Core.Eq, Int -> VaultMattersHoldsGet -> ShowS
[VaultMattersHoldsGet] -> ShowS
VaultMattersHoldsGet -> String
(Int -> VaultMattersHoldsGet -> ShowS)
-> (VaultMattersHoldsGet -> String)
-> ([VaultMattersHoldsGet] -> ShowS)
-> Show VaultMattersHoldsGet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VaultMattersHoldsGet -> ShowS
showsPrec :: Int -> VaultMattersHoldsGet -> ShowS
$cshow :: VaultMattersHoldsGet -> String
show :: VaultMattersHoldsGet -> String
$cshowList :: [VaultMattersHoldsGet] -> ShowS
showList :: [VaultMattersHoldsGet] -> ShowS
Core.Show, (forall x. VaultMattersHoldsGet -> Rep VaultMattersHoldsGet x)
-> (forall x. Rep VaultMattersHoldsGet x -> VaultMattersHoldsGet)
-> Generic VaultMattersHoldsGet
forall x. Rep VaultMattersHoldsGet x -> VaultMattersHoldsGet
forall x. VaultMattersHoldsGet -> Rep VaultMattersHoldsGet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. VaultMattersHoldsGet -> Rep VaultMattersHoldsGet x
from :: forall x. VaultMattersHoldsGet -> Rep VaultMattersHoldsGet x
$cto :: forall x. Rep VaultMattersHoldsGet x -> VaultMattersHoldsGet
to :: forall x. Rep VaultMattersHoldsGet x -> VaultMattersHoldsGet
Core.Generic)
newVaultMattersHoldsGet ::
Core.Text ->
Core.Text ->
VaultMattersHoldsGet
newVaultMattersHoldsGet :: Text -> Text -> VaultMattersHoldsGet
newVaultMattersHoldsGet Text
holdId Text
matterId =
VaultMattersHoldsGet
{ 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,
holdId :: Text
holdId = Text
holdId,
matterId :: Text
matterId = Text
matterId,
uploadType :: Maybe Text
uploadType = Maybe Text
forall a. Maybe a
Core.Nothing,
uploadProtocol :: Maybe Text
uploadProtocol = Maybe Text
forall a. Maybe a
Core.Nothing,
view :: Maybe MattersHoldsGetView
view = Maybe MattersHoldsGetView
forall a. Maybe a
Core.Nothing
}
instance Core.GoogleRequest VaultMattersHoldsGet where
type Rs VaultMattersHoldsGet = Hold
type
Scopes VaultMattersHoldsGet =
'[Ediscovery'FullControl, Ediscovery'Readonly]
requestClient :: VaultMattersHoldsGet -> GClient (Rs VaultMattersHoldsGet)
requestClient VaultMattersHoldsGet {Maybe Text
Maybe MattersHoldsGetView
Maybe Xgafv
Text
xgafv :: VaultMattersHoldsGet -> Maybe Xgafv
accessToken :: VaultMattersHoldsGet -> Maybe Text
callback :: VaultMattersHoldsGet -> Maybe Text
holdId :: VaultMattersHoldsGet -> Text
matterId :: VaultMattersHoldsGet -> Text
uploadType :: VaultMattersHoldsGet -> Maybe Text
uploadProtocol :: VaultMattersHoldsGet -> Maybe Text
view :: VaultMattersHoldsGet -> Maybe MattersHoldsGetView
xgafv :: Maybe Xgafv
accessToken :: Maybe Text
callback :: Maybe Text
holdId :: Text
matterId :: Text
uploadType :: Maybe Text
uploadProtocol :: Maybe Text
view :: Maybe MattersHoldsGetView
..} =
Text
-> Text
-> Maybe Xgafv
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe MattersHoldsGetView
-> Maybe AltJSON
-> ServiceConfig
-> GClient Hold
go
Text
matterId
Text
holdId
Maybe Xgafv
xgafv
Maybe Text
accessToken
Maybe Text
callback
Maybe Text
uploadType
Maybe Text
uploadProtocol
Maybe MattersHoldsGetView
view
(AltJSON -> Maybe AltJSON
forall a. a -> Maybe a
Core.Just AltJSON
Core.AltJSON)
ServiceConfig
vaultService
where
go :: Fn VaultMattersHoldsGetResource
go =
Proxy VaultMattersHoldsGetResource
-> Request -> Fn VaultMattersHoldsGetResource
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
Core.buildClient
(Proxy VaultMattersHoldsGetResource
forall {k} (t :: k). Proxy t
Core.Proxy :: Core.Proxy VaultMattersHoldsGetResource)
Request
forall a. Monoid a => a
Core.mempty