{-# 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.Accounts.Create
-- 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)
--
-- Adds an account to a hold. Accounts can be added only to a hold that does not have an organizational unit set. If you try to add an account to an organizational unit-based hold, an error is returned.
--
-- /See:/ <https://developers.google.com/vault Google Vault API Reference> for @vault.matters.holds.accounts.create@.
module Gogol.Vault.Matters.Holds.Accounts.Create
  ( -- * Resource
    VaultMattersHoldsAccountsCreateResource,

    -- ** Constructing a Request
    VaultMattersHoldsAccountsCreate (..),
    newVaultMattersHoldsAccountsCreate,
  )
where

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

-- | A resource alias for @vault.matters.holds.accounts.create@ method which the
-- 'VaultMattersHoldsAccountsCreate' request conforms to.
type VaultMattersHoldsAccountsCreateResource =
  "v1"
    Core.:> "matters"
    Core.:> Core.Capture "matterId" Core.Text
    Core.:> "holds"
    Core.:> Core.Capture "holdId" Core.Text
    Core.:> "accounts"
    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] HeldAccount
    Core.:> Core.Post '[Core.JSON] HeldAccount

-- | Adds an account to a hold. Accounts can be added only to a hold that does not have an organizational unit set. If you try to add an account to an organizational unit-based hold, an error is returned.
--
-- /See:/ 'newVaultMattersHoldsAccountsCreate' smart constructor.
data VaultMattersHoldsAccountsCreate = VaultMattersHoldsAccountsCreate
  { -- | V1 error format.
    VaultMattersHoldsAccountsCreate -> Maybe Xgafv
xgafv :: (Core.Maybe Xgafv),
    -- | OAuth access token.
    VaultMattersHoldsAccountsCreate -> Maybe Text
accessToken :: (Core.Maybe Core.Text),
    -- | JSONP
    VaultMattersHoldsAccountsCreate -> Maybe Text
callback :: (Core.Maybe Core.Text),
    -- | The hold ID.
    VaultMattersHoldsAccountsCreate -> Text
holdId :: Core.Text,
    -- | The matter ID.
    VaultMattersHoldsAccountsCreate -> Text
matterId :: Core.Text,
    -- | Multipart request metadata.
    VaultMattersHoldsAccountsCreate -> HeldAccount
payload :: HeldAccount,
    -- | Legacy upload protocol for media (e.g. \"media\", \"multipart\").
    VaultMattersHoldsAccountsCreate -> Maybe Text
uploadType :: (Core.Maybe Core.Text),
    -- | Upload protocol for media (e.g. \"raw\", \"multipart\").
    VaultMattersHoldsAccountsCreate -> Maybe Text
uploadProtocol :: (Core.Maybe Core.Text)
  }
  deriving (VaultMattersHoldsAccountsCreate
-> VaultMattersHoldsAccountsCreate -> Bool
(VaultMattersHoldsAccountsCreate
 -> VaultMattersHoldsAccountsCreate -> Bool)
-> (VaultMattersHoldsAccountsCreate
    -> VaultMattersHoldsAccountsCreate -> Bool)
-> Eq VaultMattersHoldsAccountsCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VaultMattersHoldsAccountsCreate
-> VaultMattersHoldsAccountsCreate -> Bool
== :: VaultMattersHoldsAccountsCreate
-> VaultMattersHoldsAccountsCreate -> Bool
$c/= :: VaultMattersHoldsAccountsCreate
-> VaultMattersHoldsAccountsCreate -> Bool
/= :: VaultMattersHoldsAccountsCreate
-> VaultMattersHoldsAccountsCreate -> Bool
Core.Eq, Int -> VaultMattersHoldsAccountsCreate -> ShowS
[VaultMattersHoldsAccountsCreate] -> ShowS
VaultMattersHoldsAccountsCreate -> String
(Int -> VaultMattersHoldsAccountsCreate -> ShowS)
-> (VaultMattersHoldsAccountsCreate -> String)
-> ([VaultMattersHoldsAccountsCreate] -> ShowS)
-> Show VaultMattersHoldsAccountsCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> VaultMattersHoldsAccountsCreate -> ShowS
showsPrec :: Int -> VaultMattersHoldsAccountsCreate -> ShowS
$cshow :: VaultMattersHoldsAccountsCreate -> String
show :: VaultMattersHoldsAccountsCreate -> String
$cshowList :: [VaultMattersHoldsAccountsCreate] -> ShowS
showList :: [VaultMattersHoldsAccountsCreate] -> ShowS
Core.Show, (forall x.
 VaultMattersHoldsAccountsCreate
 -> Rep VaultMattersHoldsAccountsCreate x)
-> (forall x.
    Rep VaultMattersHoldsAccountsCreate x
    -> VaultMattersHoldsAccountsCreate)
-> Generic VaultMattersHoldsAccountsCreate
forall x.
Rep VaultMattersHoldsAccountsCreate x
-> VaultMattersHoldsAccountsCreate
forall x.
VaultMattersHoldsAccountsCreate
-> Rep VaultMattersHoldsAccountsCreate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
VaultMattersHoldsAccountsCreate
-> Rep VaultMattersHoldsAccountsCreate x
from :: forall x.
VaultMattersHoldsAccountsCreate
-> Rep VaultMattersHoldsAccountsCreate x
$cto :: forall x.
Rep VaultMattersHoldsAccountsCreate x
-> VaultMattersHoldsAccountsCreate
to :: forall x.
Rep VaultMattersHoldsAccountsCreate x
-> VaultMattersHoldsAccountsCreate
Core.Generic)

-- | Creates a value of 'VaultMattersHoldsAccountsCreate' with the minimum fields required to make a request.
newVaultMattersHoldsAccountsCreate ::
  -- |  The hold ID. See 'holdId'.
  Core.Text ->
  -- |  The matter ID. See 'matterId'.
  Core.Text ->
  -- |  Multipart request metadata. See 'payload'.
  HeldAccount ->
  VaultMattersHoldsAccountsCreate
newVaultMattersHoldsAccountsCreate :: Text -> Text -> HeldAccount -> VaultMattersHoldsAccountsCreate
newVaultMattersHoldsAccountsCreate Text
holdId Text
matterId HeldAccount
payload =
  VaultMattersHoldsAccountsCreate
    { 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,
      payload :: HeldAccount
payload = HeldAccount
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 VaultMattersHoldsAccountsCreate where
  type Rs VaultMattersHoldsAccountsCreate = HeldAccount
  type
    Scopes VaultMattersHoldsAccountsCreate =
      '[Ediscovery'FullControl]
  requestClient :: VaultMattersHoldsAccountsCreate
-> GClient (Rs VaultMattersHoldsAccountsCreate)
requestClient VaultMattersHoldsAccountsCreate {Maybe Text
Maybe Xgafv
Text
HeldAccount
xgafv :: VaultMattersHoldsAccountsCreate -> Maybe Xgafv
accessToken :: VaultMattersHoldsAccountsCreate -> Maybe Text
callback :: VaultMattersHoldsAccountsCreate -> Maybe Text
holdId :: VaultMattersHoldsAccountsCreate -> Text
matterId :: VaultMattersHoldsAccountsCreate -> Text
payload :: VaultMattersHoldsAccountsCreate -> HeldAccount
uploadType :: VaultMattersHoldsAccountsCreate -> Maybe Text
uploadProtocol :: VaultMattersHoldsAccountsCreate -> Maybe Text
xgafv :: Maybe Xgafv
accessToken :: Maybe Text
callback :: Maybe Text
holdId :: Text
matterId :: Text
payload :: HeldAccount
uploadType :: Maybe Text
uploadProtocol :: Maybe Text
..} =
    Text
-> Text
-> Maybe Xgafv
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe AltJSON
-> HeldAccount
-> ServiceConfig
-> GClient HeldAccount
go
      Text
matterId
      Text
holdId
      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)
      HeldAccount
payload
      ServiceConfig
vaultService
    where
      go :: Fn VaultMattersHoldsAccountsCreateResource
go =
        Proxy VaultMattersHoldsAccountsCreateResource
-> Request -> Fn VaultMattersHoldsAccountsCreateResource
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
Core.buildClient
          (Proxy VaultMattersHoldsAccountsCreateResource
forall {k} (t :: k). Proxy t
Core.Proxy :: Core.Proxy VaultMattersHoldsAccountsCreateResource)
          Request
forall a. Monoid a => a
Core.mempty