{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Connect.UpdateSecurityProfile
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This API is in preview release for Amazon Connect and is subject to
-- change.
--
-- Updates a security profile.
module Amazonka.Connect.UpdateSecurityProfile
  ( -- * Creating a Request
    UpdateSecurityProfile (..),
    newUpdateSecurityProfile,

    -- * Request Lenses
    updateSecurityProfile_allowedAccessControlTags,
    updateSecurityProfile_description,
    updateSecurityProfile_permissions,
    updateSecurityProfile_tagRestrictedResources,
    updateSecurityProfile_securityProfileId,
    updateSecurityProfile_instanceId,

    -- * Destructuring the Response
    UpdateSecurityProfileResponse (..),
    newUpdateSecurityProfileResponse,
  )
where

import Amazonka.Connect.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateSecurityProfile' smart constructor.
data UpdateSecurityProfile = UpdateSecurityProfile'
  { -- | The list of tags that a security profile uses to restrict access to
    -- resources in Amazon Connect.
    UpdateSecurityProfile -> Maybe (HashMap Text Text)
allowedAccessControlTags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The description of the security profile.
    UpdateSecurityProfile -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The permissions granted to a security profile. For a list of valid
    -- permissions, see
    -- <https://docs.aws.amazon.com/connect/latest/adminguide/security-profile-list.html List of security profile permissions>.
    UpdateSecurityProfile -> Maybe [Text]
permissions :: Prelude.Maybe [Prelude.Text],
    -- | The list of resources that a security profile applies tag restrictions
    -- to in Amazon Connect.
    UpdateSecurityProfile -> Maybe [Text]
tagRestrictedResources :: Prelude.Maybe [Prelude.Text],
    -- | The identifier for the security profle.
    UpdateSecurityProfile -> Text
securityProfileId :: Prelude.Text,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    UpdateSecurityProfile -> Text
instanceId :: Prelude.Text
  }
  deriving (UpdateSecurityProfile -> UpdateSecurityProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSecurityProfile -> UpdateSecurityProfile -> Bool
$c/= :: UpdateSecurityProfile -> UpdateSecurityProfile -> Bool
== :: UpdateSecurityProfile -> UpdateSecurityProfile -> Bool
$c== :: UpdateSecurityProfile -> UpdateSecurityProfile -> Bool
Prelude.Eq, ReadPrec [UpdateSecurityProfile]
ReadPrec UpdateSecurityProfile
Int -> ReadS UpdateSecurityProfile
ReadS [UpdateSecurityProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSecurityProfile]
$creadListPrec :: ReadPrec [UpdateSecurityProfile]
readPrec :: ReadPrec UpdateSecurityProfile
$creadPrec :: ReadPrec UpdateSecurityProfile
readList :: ReadS [UpdateSecurityProfile]
$creadList :: ReadS [UpdateSecurityProfile]
readsPrec :: Int -> ReadS UpdateSecurityProfile
$creadsPrec :: Int -> ReadS UpdateSecurityProfile
Prelude.Read, Int -> UpdateSecurityProfile -> ShowS
[UpdateSecurityProfile] -> ShowS
UpdateSecurityProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSecurityProfile] -> ShowS
$cshowList :: [UpdateSecurityProfile] -> ShowS
show :: UpdateSecurityProfile -> String
$cshow :: UpdateSecurityProfile -> String
showsPrec :: Int -> UpdateSecurityProfile -> ShowS
$cshowsPrec :: Int -> UpdateSecurityProfile -> ShowS
Prelude.Show, forall x. Rep UpdateSecurityProfile x -> UpdateSecurityProfile
forall x. UpdateSecurityProfile -> Rep UpdateSecurityProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateSecurityProfile x -> UpdateSecurityProfile
$cfrom :: forall x. UpdateSecurityProfile -> Rep UpdateSecurityProfile x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSecurityProfile' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'allowedAccessControlTags', 'updateSecurityProfile_allowedAccessControlTags' - The list of tags that a security profile uses to restrict access to
-- resources in Amazon Connect.
--
-- 'description', 'updateSecurityProfile_description' - The description of the security profile.
--
-- 'permissions', 'updateSecurityProfile_permissions' - The permissions granted to a security profile. For a list of valid
-- permissions, see
-- <https://docs.aws.amazon.com/connect/latest/adminguide/security-profile-list.html List of security profile permissions>.
--
-- 'tagRestrictedResources', 'updateSecurityProfile_tagRestrictedResources' - The list of resources that a security profile applies tag restrictions
-- to in Amazon Connect.
--
-- 'securityProfileId', 'updateSecurityProfile_securityProfileId' - The identifier for the security profle.
--
-- 'instanceId', 'updateSecurityProfile_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
newUpdateSecurityProfile ::
  -- | 'securityProfileId'
  Prelude.Text ->
  -- | 'instanceId'
  Prelude.Text ->
  UpdateSecurityProfile
newUpdateSecurityProfile :: Text -> Text -> UpdateSecurityProfile
newUpdateSecurityProfile
  Text
pSecurityProfileId_
  Text
pInstanceId_ =
    UpdateSecurityProfile'
      { $sel:allowedAccessControlTags:UpdateSecurityProfile' :: Maybe (HashMap Text Text)
allowedAccessControlTags =
          forall a. Maybe a
Prelude.Nothing,
        $sel:description:UpdateSecurityProfile' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:permissions:UpdateSecurityProfile' :: Maybe [Text]
permissions = forall a. Maybe a
Prelude.Nothing,
        $sel:tagRestrictedResources:UpdateSecurityProfile' :: Maybe [Text]
tagRestrictedResources = forall a. Maybe a
Prelude.Nothing,
        $sel:securityProfileId:UpdateSecurityProfile' :: Text
securityProfileId = Text
pSecurityProfileId_,
        $sel:instanceId:UpdateSecurityProfile' :: Text
instanceId = Text
pInstanceId_
      }

-- | The list of tags that a security profile uses to restrict access to
-- resources in Amazon Connect.
updateSecurityProfile_allowedAccessControlTags :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
updateSecurityProfile_allowedAccessControlTags :: Lens' UpdateSecurityProfile (Maybe (HashMap Text Text))
updateSecurityProfile_allowedAccessControlTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe (HashMap Text Text)
allowedAccessControlTags :: Maybe (HashMap Text Text)
$sel:allowedAccessControlTags:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe (HashMap Text Text)
allowedAccessControlTags} -> Maybe (HashMap Text Text)
allowedAccessControlTags) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe (HashMap Text Text)
a -> UpdateSecurityProfile
s {$sel:allowedAccessControlTags:UpdateSecurityProfile' :: Maybe (HashMap Text Text)
allowedAccessControlTags = Maybe (HashMap Text Text)
a} :: UpdateSecurityProfile) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The description of the security profile.
updateSecurityProfile_description :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe Prelude.Text)
updateSecurityProfile_description :: Lens' UpdateSecurityProfile (Maybe Text)
updateSecurityProfile_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe Text
description :: Maybe Text
$sel:description:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe Text
a -> UpdateSecurityProfile
s {$sel:description:UpdateSecurityProfile' :: Maybe Text
description = Maybe Text
a} :: UpdateSecurityProfile)

-- | The permissions granted to a security profile. For a list of valid
-- permissions, see
-- <https://docs.aws.amazon.com/connect/latest/adminguide/security-profile-list.html List of security profile permissions>.
updateSecurityProfile_permissions :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe [Prelude.Text])
updateSecurityProfile_permissions :: Lens' UpdateSecurityProfile (Maybe [Text])
updateSecurityProfile_permissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe [Text]
permissions :: Maybe [Text]
$sel:permissions:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
permissions} -> Maybe [Text]
permissions) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe [Text]
a -> UpdateSecurityProfile
s {$sel:permissions:UpdateSecurityProfile' :: Maybe [Text]
permissions = Maybe [Text]
a} :: UpdateSecurityProfile) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The list of resources that a security profile applies tag restrictions
-- to in Amazon Connect.
updateSecurityProfile_tagRestrictedResources :: Lens.Lens' UpdateSecurityProfile (Prelude.Maybe [Prelude.Text])
updateSecurityProfile_tagRestrictedResources :: Lens' UpdateSecurityProfile (Maybe [Text])
updateSecurityProfile_tagRestrictedResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Maybe [Text]
tagRestrictedResources :: Maybe [Text]
$sel:tagRestrictedResources:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
tagRestrictedResources} -> Maybe [Text]
tagRestrictedResources) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Maybe [Text]
a -> UpdateSecurityProfile
s {$sel:tagRestrictedResources:UpdateSecurityProfile' :: Maybe [Text]
tagRestrictedResources = Maybe [Text]
a} :: UpdateSecurityProfile) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The identifier for the security profle.
updateSecurityProfile_securityProfileId :: Lens.Lens' UpdateSecurityProfile Prelude.Text
updateSecurityProfile_securityProfileId :: Lens' UpdateSecurityProfile Text
updateSecurityProfile_securityProfileId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Text
securityProfileId :: Text
$sel:securityProfileId:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
securityProfileId} -> Text
securityProfileId) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Text
a -> UpdateSecurityProfile
s {$sel:securityProfileId:UpdateSecurityProfile' :: Text
securityProfileId = Text
a} :: UpdateSecurityProfile)

-- | The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
updateSecurityProfile_instanceId :: Lens.Lens' UpdateSecurityProfile Prelude.Text
updateSecurityProfile_instanceId :: Lens' UpdateSecurityProfile Text
updateSecurityProfile_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityProfile' {Text
instanceId :: Text
$sel:instanceId:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
instanceId} -> Text
instanceId) (\s :: UpdateSecurityProfile
s@UpdateSecurityProfile' {} Text
a -> UpdateSecurityProfile
s {$sel:instanceId:UpdateSecurityProfile' :: Text
instanceId = Text
a} :: UpdateSecurityProfile)

instance Core.AWSRequest UpdateSecurityProfile where
  type
    AWSResponse UpdateSecurityProfile =
      UpdateSecurityProfileResponse
  request :: (Service -> Service)
-> UpdateSecurityProfile -> Request UpdateSecurityProfile
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateSecurityProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateSecurityProfile)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull UpdateSecurityProfileResponse
UpdateSecurityProfileResponse'

instance Prelude.Hashable UpdateSecurityProfile where
  hashWithSalt :: Int -> UpdateSecurityProfile -> Int
hashWithSalt Int
_salt UpdateSecurityProfile' {Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
instanceId :: Text
securityProfileId :: Text
tagRestrictedResources :: Maybe [Text]
permissions :: Maybe [Text]
description :: Maybe Text
allowedAccessControlTags :: Maybe (HashMap Text Text)
$sel:instanceId:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:securityProfileId:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:tagRestrictedResources:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
$sel:permissions:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
$sel:description:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
$sel:allowedAccessControlTags:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
allowedAccessControlTags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
permissions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
tagRestrictedResources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
securityProfileId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

instance Prelude.NFData UpdateSecurityProfile where
  rnf :: UpdateSecurityProfile -> ()
rnf UpdateSecurityProfile' {Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
instanceId :: Text
securityProfileId :: Text
tagRestrictedResources :: Maybe [Text]
permissions :: Maybe [Text]
description :: Maybe Text
allowedAccessControlTags :: Maybe (HashMap Text Text)
$sel:instanceId:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:securityProfileId:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:tagRestrictedResources:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
$sel:permissions:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
$sel:description:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
$sel:allowedAccessControlTags:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
allowedAccessControlTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
permissions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
tagRestrictedResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
securityProfileId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId

instance Data.ToHeaders UpdateSecurityProfile where
  toHeaders :: UpdateSecurityProfile -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateSecurityProfile where
  toJSON :: UpdateSecurityProfile -> Value
toJSON UpdateSecurityProfile' {Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
instanceId :: Text
securityProfileId :: Text
tagRestrictedResources :: Maybe [Text]
permissions :: Maybe [Text]
description :: Maybe Text
allowedAccessControlTags :: Maybe (HashMap Text Text)
$sel:instanceId:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:securityProfileId:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:tagRestrictedResources:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
$sel:permissions:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
$sel:description:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
$sel:allowedAccessControlTags:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AllowedAccessControlTags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
allowedAccessControlTags,
            (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
description,
            (Key
"Permissions" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
permissions,
            (Key
"TagRestrictedResources" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
tagRestrictedResources
          ]
      )

instance Data.ToPath UpdateSecurityProfile where
  toPath :: UpdateSecurityProfile -> ByteString
toPath UpdateSecurityProfile' {Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
instanceId :: Text
securityProfileId :: Text
tagRestrictedResources :: Maybe [Text]
permissions :: Maybe [Text]
description :: Maybe Text
allowedAccessControlTags :: Maybe (HashMap Text Text)
$sel:instanceId:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:securityProfileId:UpdateSecurityProfile' :: UpdateSecurityProfile -> Text
$sel:tagRestrictedResources:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
$sel:permissions:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe [Text]
$sel:description:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe Text
$sel:allowedAccessControlTags:UpdateSecurityProfile' :: UpdateSecurityProfile -> Maybe (HashMap Text Text)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/security-profiles/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
securityProfileId
      ]

instance Data.ToQuery UpdateSecurityProfile where
  toQuery :: UpdateSecurityProfile -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateSecurityProfileResponse' smart constructor.
data UpdateSecurityProfileResponse = UpdateSecurityProfileResponse'
  {
  }
  deriving (UpdateSecurityProfileResponse
-> UpdateSecurityProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSecurityProfileResponse
-> UpdateSecurityProfileResponse -> Bool
$c/= :: UpdateSecurityProfileResponse
-> UpdateSecurityProfileResponse -> Bool
== :: UpdateSecurityProfileResponse
-> UpdateSecurityProfileResponse -> Bool
$c== :: UpdateSecurityProfileResponse
-> UpdateSecurityProfileResponse -> Bool
Prelude.Eq, ReadPrec [UpdateSecurityProfileResponse]
ReadPrec UpdateSecurityProfileResponse
Int -> ReadS UpdateSecurityProfileResponse
ReadS [UpdateSecurityProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSecurityProfileResponse]
$creadListPrec :: ReadPrec [UpdateSecurityProfileResponse]
readPrec :: ReadPrec UpdateSecurityProfileResponse
$creadPrec :: ReadPrec UpdateSecurityProfileResponse
readList :: ReadS [UpdateSecurityProfileResponse]
$creadList :: ReadS [UpdateSecurityProfileResponse]
readsPrec :: Int -> ReadS UpdateSecurityProfileResponse
$creadsPrec :: Int -> ReadS UpdateSecurityProfileResponse
Prelude.Read, Int -> UpdateSecurityProfileResponse -> ShowS
[UpdateSecurityProfileResponse] -> ShowS
UpdateSecurityProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSecurityProfileResponse] -> ShowS
$cshowList :: [UpdateSecurityProfileResponse] -> ShowS
show :: UpdateSecurityProfileResponse -> String
$cshow :: UpdateSecurityProfileResponse -> String
showsPrec :: Int -> UpdateSecurityProfileResponse -> ShowS
$cshowsPrec :: Int -> UpdateSecurityProfileResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateSecurityProfileResponse x
-> UpdateSecurityProfileResponse
forall x.
UpdateSecurityProfileResponse
-> Rep UpdateSecurityProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateSecurityProfileResponse x
-> UpdateSecurityProfileResponse
$cfrom :: forall x.
UpdateSecurityProfileResponse
-> Rep UpdateSecurityProfileResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSecurityProfileResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
newUpdateSecurityProfileResponse ::
  UpdateSecurityProfileResponse
newUpdateSecurityProfileResponse :: UpdateSecurityProfileResponse
newUpdateSecurityProfileResponse =
  UpdateSecurityProfileResponse
UpdateSecurityProfileResponse'

instance Prelude.NFData UpdateSecurityProfileResponse where
  rnf :: UpdateSecurityProfileResponse -> ()
rnf UpdateSecurityProfileResponse
_ = ()