{-# 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.StorageGateway.UpdateSMBSecurityStrategy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the SMB security strategy on a file gateway. This action is only
-- supported in file gateways.
--
-- This API is called Security level in the User Guide.
--
-- A higher security level can affect performance of the gateway.
module Amazonka.StorageGateway.UpdateSMBSecurityStrategy
  ( -- * Creating a Request
    UpdateSMBSecurityStrategy (..),
    newUpdateSMBSecurityStrategy,

    -- * Request Lenses
    updateSMBSecurityStrategy_gatewayARN,
    updateSMBSecurityStrategy_sMBSecurityStrategy,

    -- * Destructuring the Response
    UpdateSMBSecurityStrategyResponse (..),
    newUpdateSMBSecurityStrategyResponse,

    -- * Response Lenses
    updateSMBSecurityStrategyResponse_gatewayARN,
    updateSMBSecurityStrategyResponse_httpStatus,
  )
where

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
import Amazonka.StorageGateway.Types

-- | /See:/ 'newUpdateSMBSecurityStrategy' smart constructor.
data UpdateSMBSecurityStrategy = UpdateSMBSecurityStrategy'
  { UpdateSMBSecurityStrategy -> Text
gatewayARN :: Prelude.Text,
    -- | Specifies the type of security strategy.
    --
    -- ClientSpecified: if you use this option, requests are established based
    -- on what is negotiated by the client. This option is recommended when you
    -- want to maximize compatibility across different clients in your
    -- environment. Supported only in S3 File Gateway.
    --
    -- MandatorySigning: if you use this option, file gateway only allows
    -- connections from SMBv2 or SMBv3 clients that have signing enabled. This
    -- option works with SMB clients on Microsoft Windows Vista, Windows Server
    -- 2008 or newer.
    --
    -- MandatoryEncryption: if you use this option, file gateway only allows
    -- connections from SMBv3 clients that have encryption enabled. This option
    -- is highly recommended for environments that handle sensitive data. This
    -- option works with SMB clients on Microsoft Windows 8, Windows Server
    -- 2012 or newer.
    UpdateSMBSecurityStrategy -> SMBSecurityStrategy
sMBSecurityStrategy :: SMBSecurityStrategy
  }
  deriving (UpdateSMBSecurityStrategy -> UpdateSMBSecurityStrategy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSMBSecurityStrategy -> UpdateSMBSecurityStrategy -> Bool
$c/= :: UpdateSMBSecurityStrategy -> UpdateSMBSecurityStrategy -> Bool
== :: UpdateSMBSecurityStrategy -> UpdateSMBSecurityStrategy -> Bool
$c== :: UpdateSMBSecurityStrategy -> UpdateSMBSecurityStrategy -> Bool
Prelude.Eq, ReadPrec [UpdateSMBSecurityStrategy]
ReadPrec UpdateSMBSecurityStrategy
Int -> ReadS UpdateSMBSecurityStrategy
ReadS [UpdateSMBSecurityStrategy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSMBSecurityStrategy]
$creadListPrec :: ReadPrec [UpdateSMBSecurityStrategy]
readPrec :: ReadPrec UpdateSMBSecurityStrategy
$creadPrec :: ReadPrec UpdateSMBSecurityStrategy
readList :: ReadS [UpdateSMBSecurityStrategy]
$creadList :: ReadS [UpdateSMBSecurityStrategy]
readsPrec :: Int -> ReadS UpdateSMBSecurityStrategy
$creadsPrec :: Int -> ReadS UpdateSMBSecurityStrategy
Prelude.Read, Int -> UpdateSMBSecurityStrategy -> ShowS
[UpdateSMBSecurityStrategy] -> ShowS
UpdateSMBSecurityStrategy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSMBSecurityStrategy] -> ShowS
$cshowList :: [UpdateSMBSecurityStrategy] -> ShowS
show :: UpdateSMBSecurityStrategy -> String
$cshow :: UpdateSMBSecurityStrategy -> String
showsPrec :: Int -> UpdateSMBSecurityStrategy -> ShowS
$cshowsPrec :: Int -> UpdateSMBSecurityStrategy -> ShowS
Prelude.Show, forall x.
Rep UpdateSMBSecurityStrategy x -> UpdateSMBSecurityStrategy
forall x.
UpdateSMBSecurityStrategy -> Rep UpdateSMBSecurityStrategy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateSMBSecurityStrategy x -> UpdateSMBSecurityStrategy
$cfrom :: forall x.
UpdateSMBSecurityStrategy -> Rep UpdateSMBSecurityStrategy x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSMBSecurityStrategy' 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:
--
-- 'gatewayARN', 'updateSMBSecurityStrategy_gatewayARN' - Undocumented member.
--
-- 'sMBSecurityStrategy', 'updateSMBSecurityStrategy_sMBSecurityStrategy' - Specifies the type of security strategy.
--
-- ClientSpecified: if you use this option, requests are established based
-- on what is negotiated by the client. This option is recommended when you
-- want to maximize compatibility across different clients in your
-- environment. Supported only in S3 File Gateway.
--
-- MandatorySigning: if you use this option, file gateway only allows
-- connections from SMBv2 or SMBv3 clients that have signing enabled. This
-- option works with SMB clients on Microsoft Windows Vista, Windows Server
-- 2008 or newer.
--
-- MandatoryEncryption: if you use this option, file gateway only allows
-- connections from SMBv3 clients that have encryption enabled. This option
-- is highly recommended for environments that handle sensitive data. This
-- option works with SMB clients on Microsoft Windows 8, Windows Server
-- 2012 or newer.
newUpdateSMBSecurityStrategy ::
  -- | 'gatewayARN'
  Prelude.Text ->
  -- | 'sMBSecurityStrategy'
  SMBSecurityStrategy ->
  UpdateSMBSecurityStrategy
newUpdateSMBSecurityStrategy :: Text -> SMBSecurityStrategy -> UpdateSMBSecurityStrategy
newUpdateSMBSecurityStrategy
  Text
pGatewayARN_
  SMBSecurityStrategy
pSMBSecurityStrategy_ =
    UpdateSMBSecurityStrategy'
      { $sel:gatewayARN:UpdateSMBSecurityStrategy' :: Text
gatewayARN =
          Text
pGatewayARN_,
        $sel:sMBSecurityStrategy:UpdateSMBSecurityStrategy' :: SMBSecurityStrategy
sMBSecurityStrategy = SMBSecurityStrategy
pSMBSecurityStrategy_
      }

-- | Undocumented member.
updateSMBSecurityStrategy_gatewayARN :: Lens.Lens' UpdateSMBSecurityStrategy Prelude.Text
updateSMBSecurityStrategy_gatewayARN :: Lens' UpdateSMBSecurityStrategy Text
updateSMBSecurityStrategy_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSMBSecurityStrategy' {Text
gatewayARN :: Text
$sel:gatewayARN:UpdateSMBSecurityStrategy' :: UpdateSMBSecurityStrategy -> Text
gatewayARN} -> Text
gatewayARN) (\s :: UpdateSMBSecurityStrategy
s@UpdateSMBSecurityStrategy' {} Text
a -> UpdateSMBSecurityStrategy
s {$sel:gatewayARN:UpdateSMBSecurityStrategy' :: Text
gatewayARN = Text
a} :: UpdateSMBSecurityStrategy)

-- | Specifies the type of security strategy.
--
-- ClientSpecified: if you use this option, requests are established based
-- on what is negotiated by the client. This option is recommended when you
-- want to maximize compatibility across different clients in your
-- environment. Supported only in S3 File Gateway.
--
-- MandatorySigning: if you use this option, file gateway only allows
-- connections from SMBv2 or SMBv3 clients that have signing enabled. This
-- option works with SMB clients on Microsoft Windows Vista, Windows Server
-- 2008 or newer.
--
-- MandatoryEncryption: if you use this option, file gateway only allows
-- connections from SMBv3 clients that have encryption enabled. This option
-- is highly recommended for environments that handle sensitive data. This
-- option works with SMB clients on Microsoft Windows 8, Windows Server
-- 2012 or newer.
updateSMBSecurityStrategy_sMBSecurityStrategy :: Lens.Lens' UpdateSMBSecurityStrategy SMBSecurityStrategy
updateSMBSecurityStrategy_sMBSecurityStrategy :: Lens' UpdateSMBSecurityStrategy SMBSecurityStrategy
updateSMBSecurityStrategy_sMBSecurityStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSMBSecurityStrategy' {SMBSecurityStrategy
sMBSecurityStrategy :: SMBSecurityStrategy
$sel:sMBSecurityStrategy:UpdateSMBSecurityStrategy' :: UpdateSMBSecurityStrategy -> SMBSecurityStrategy
sMBSecurityStrategy} -> SMBSecurityStrategy
sMBSecurityStrategy) (\s :: UpdateSMBSecurityStrategy
s@UpdateSMBSecurityStrategy' {} SMBSecurityStrategy
a -> UpdateSMBSecurityStrategy
s {$sel:sMBSecurityStrategy:UpdateSMBSecurityStrategy' :: SMBSecurityStrategy
sMBSecurityStrategy = SMBSecurityStrategy
a} :: UpdateSMBSecurityStrategy)

instance Core.AWSRequest UpdateSMBSecurityStrategy where
  type
    AWSResponse UpdateSMBSecurityStrategy =
      UpdateSMBSecurityStrategyResponse
  request :: (Service -> Service)
-> UpdateSMBSecurityStrategy -> Request UpdateSMBSecurityStrategy
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 UpdateSMBSecurityStrategy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateSMBSecurityStrategy)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> UpdateSMBSecurityStrategyResponse
UpdateSMBSecurityStrategyResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"GatewayARN")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable UpdateSMBSecurityStrategy where
  hashWithSalt :: Int -> UpdateSMBSecurityStrategy -> Int
hashWithSalt Int
_salt UpdateSMBSecurityStrategy' {Text
SMBSecurityStrategy
sMBSecurityStrategy :: SMBSecurityStrategy
gatewayARN :: Text
$sel:sMBSecurityStrategy:UpdateSMBSecurityStrategy' :: UpdateSMBSecurityStrategy -> SMBSecurityStrategy
$sel:gatewayARN:UpdateSMBSecurityStrategy' :: UpdateSMBSecurityStrategy -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gatewayARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SMBSecurityStrategy
sMBSecurityStrategy

instance Prelude.NFData UpdateSMBSecurityStrategy where
  rnf :: UpdateSMBSecurityStrategy -> ()
rnf UpdateSMBSecurityStrategy' {Text
SMBSecurityStrategy
sMBSecurityStrategy :: SMBSecurityStrategy
gatewayARN :: Text
$sel:sMBSecurityStrategy:UpdateSMBSecurityStrategy' :: UpdateSMBSecurityStrategy -> SMBSecurityStrategy
$sel:gatewayARN:UpdateSMBSecurityStrategy' :: UpdateSMBSecurityStrategy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
gatewayARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SMBSecurityStrategy
sMBSecurityStrategy

instance Data.ToHeaders UpdateSMBSecurityStrategy where
  toHeaders :: UpdateSMBSecurityStrategy -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"StorageGateway_20130630.UpdateSMBSecurityStrategy" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateSMBSecurityStrategy where
  toJSON :: UpdateSMBSecurityStrategy -> Value
toJSON UpdateSMBSecurityStrategy' {Text
SMBSecurityStrategy
sMBSecurityStrategy :: SMBSecurityStrategy
gatewayARN :: Text
$sel:sMBSecurityStrategy:UpdateSMBSecurityStrategy' :: UpdateSMBSecurityStrategy -> SMBSecurityStrategy
$sel:gatewayARN:UpdateSMBSecurityStrategy' :: UpdateSMBSecurityStrategy -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"GatewayARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
gatewayARN),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"SMBSecurityStrategy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= SMBSecurityStrategy
sMBSecurityStrategy)
          ]
      )

instance Data.ToPath UpdateSMBSecurityStrategy where
  toPath :: UpdateSMBSecurityStrategy -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newUpdateSMBSecurityStrategyResponse' smart constructor.
data UpdateSMBSecurityStrategyResponse = UpdateSMBSecurityStrategyResponse'
  { UpdateSMBSecurityStrategyResponse -> Maybe Text
gatewayARN :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateSMBSecurityStrategyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateSMBSecurityStrategyResponse
-> UpdateSMBSecurityStrategyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSMBSecurityStrategyResponse
-> UpdateSMBSecurityStrategyResponse -> Bool
$c/= :: UpdateSMBSecurityStrategyResponse
-> UpdateSMBSecurityStrategyResponse -> Bool
== :: UpdateSMBSecurityStrategyResponse
-> UpdateSMBSecurityStrategyResponse -> Bool
$c== :: UpdateSMBSecurityStrategyResponse
-> UpdateSMBSecurityStrategyResponse -> Bool
Prelude.Eq, ReadPrec [UpdateSMBSecurityStrategyResponse]
ReadPrec UpdateSMBSecurityStrategyResponse
Int -> ReadS UpdateSMBSecurityStrategyResponse
ReadS [UpdateSMBSecurityStrategyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSMBSecurityStrategyResponse]
$creadListPrec :: ReadPrec [UpdateSMBSecurityStrategyResponse]
readPrec :: ReadPrec UpdateSMBSecurityStrategyResponse
$creadPrec :: ReadPrec UpdateSMBSecurityStrategyResponse
readList :: ReadS [UpdateSMBSecurityStrategyResponse]
$creadList :: ReadS [UpdateSMBSecurityStrategyResponse]
readsPrec :: Int -> ReadS UpdateSMBSecurityStrategyResponse
$creadsPrec :: Int -> ReadS UpdateSMBSecurityStrategyResponse
Prelude.Read, Int -> UpdateSMBSecurityStrategyResponse -> ShowS
[UpdateSMBSecurityStrategyResponse] -> ShowS
UpdateSMBSecurityStrategyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSMBSecurityStrategyResponse] -> ShowS
$cshowList :: [UpdateSMBSecurityStrategyResponse] -> ShowS
show :: UpdateSMBSecurityStrategyResponse -> String
$cshow :: UpdateSMBSecurityStrategyResponse -> String
showsPrec :: Int -> UpdateSMBSecurityStrategyResponse -> ShowS
$cshowsPrec :: Int -> UpdateSMBSecurityStrategyResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateSMBSecurityStrategyResponse x
-> UpdateSMBSecurityStrategyResponse
forall x.
UpdateSMBSecurityStrategyResponse
-> Rep UpdateSMBSecurityStrategyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateSMBSecurityStrategyResponse x
-> UpdateSMBSecurityStrategyResponse
$cfrom :: forall x.
UpdateSMBSecurityStrategyResponse
-> Rep UpdateSMBSecurityStrategyResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSMBSecurityStrategyResponse' 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:
--
-- 'gatewayARN', 'updateSMBSecurityStrategyResponse_gatewayARN' - Undocumented member.
--
-- 'httpStatus', 'updateSMBSecurityStrategyResponse_httpStatus' - The response's http status code.
newUpdateSMBSecurityStrategyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateSMBSecurityStrategyResponse
newUpdateSMBSecurityStrategyResponse :: Int -> UpdateSMBSecurityStrategyResponse
newUpdateSMBSecurityStrategyResponse Int
pHttpStatus_ =
  UpdateSMBSecurityStrategyResponse'
    { $sel:gatewayARN:UpdateSMBSecurityStrategyResponse' :: Maybe Text
gatewayARN =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateSMBSecurityStrategyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
updateSMBSecurityStrategyResponse_gatewayARN :: Lens.Lens' UpdateSMBSecurityStrategyResponse (Prelude.Maybe Prelude.Text)
updateSMBSecurityStrategyResponse_gatewayARN :: Lens' UpdateSMBSecurityStrategyResponse (Maybe Text)
updateSMBSecurityStrategyResponse_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSMBSecurityStrategyResponse' {Maybe Text
gatewayARN :: Maybe Text
$sel:gatewayARN:UpdateSMBSecurityStrategyResponse' :: UpdateSMBSecurityStrategyResponse -> Maybe Text
gatewayARN} -> Maybe Text
gatewayARN) (\s :: UpdateSMBSecurityStrategyResponse
s@UpdateSMBSecurityStrategyResponse' {} Maybe Text
a -> UpdateSMBSecurityStrategyResponse
s {$sel:gatewayARN:UpdateSMBSecurityStrategyResponse' :: Maybe Text
gatewayARN = Maybe Text
a} :: UpdateSMBSecurityStrategyResponse)

-- | The response's http status code.
updateSMBSecurityStrategyResponse_httpStatus :: Lens.Lens' UpdateSMBSecurityStrategyResponse Prelude.Int
updateSMBSecurityStrategyResponse_httpStatus :: Lens' UpdateSMBSecurityStrategyResponse Int
updateSMBSecurityStrategyResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSMBSecurityStrategyResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateSMBSecurityStrategyResponse' :: UpdateSMBSecurityStrategyResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateSMBSecurityStrategyResponse
s@UpdateSMBSecurityStrategyResponse' {} Int
a -> UpdateSMBSecurityStrategyResponse
s {$sel:httpStatus:UpdateSMBSecurityStrategyResponse' :: Int
httpStatus = Int
a} :: UpdateSMBSecurityStrategyResponse)

instance
  Prelude.NFData
    UpdateSMBSecurityStrategyResponse
  where
  rnf :: UpdateSMBSecurityStrategyResponse -> ()
rnf UpdateSMBSecurityStrategyResponse' {Int
Maybe Text
httpStatus :: Int
gatewayARN :: Maybe Text
$sel:httpStatus:UpdateSMBSecurityStrategyResponse' :: UpdateSMBSecurityStrategyResponse -> Int
$sel:gatewayARN:UpdateSMBSecurityStrategyResponse' :: UpdateSMBSecurityStrategyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gatewayARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus