{-# 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.EC2.DisassociateTrunkInterface
-- 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 action is currently in __limited preview only__. If you are
-- interested in using this feature, contact your account manager.
--
-- Removes an association between a branch network interface with a trunk
-- network interface.
module Amazonka.EC2.DisassociateTrunkInterface
  ( -- * Creating a Request
    DisassociateTrunkInterface (..),
    newDisassociateTrunkInterface,

    -- * Request Lenses
    disassociateTrunkInterface_clientToken,
    disassociateTrunkInterface_dryRun,
    disassociateTrunkInterface_associationId,

    -- * Destructuring the Response
    DisassociateTrunkInterfaceResponse (..),
    newDisassociateTrunkInterfaceResponse,

    -- * Response Lenses
    disassociateTrunkInterfaceResponse_clientToken,
    disassociateTrunkInterfaceResponse_return,
    disassociateTrunkInterfaceResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDisassociateTrunkInterface' smart constructor.
data DisassociateTrunkInterface = DisassociateTrunkInterface'
  { -- | Unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Run_Instance_Idempotency.html How to Ensure Idempotency>.
    DisassociateTrunkInterface -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    DisassociateTrunkInterface -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the association
    DisassociateTrunkInterface -> Text
associationId :: Prelude.Text
  }
  deriving (DisassociateTrunkInterface -> DisassociateTrunkInterface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateTrunkInterface -> DisassociateTrunkInterface -> Bool
$c/= :: DisassociateTrunkInterface -> DisassociateTrunkInterface -> Bool
== :: DisassociateTrunkInterface -> DisassociateTrunkInterface -> Bool
$c== :: DisassociateTrunkInterface -> DisassociateTrunkInterface -> Bool
Prelude.Eq, ReadPrec [DisassociateTrunkInterface]
ReadPrec DisassociateTrunkInterface
Int -> ReadS DisassociateTrunkInterface
ReadS [DisassociateTrunkInterface]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateTrunkInterface]
$creadListPrec :: ReadPrec [DisassociateTrunkInterface]
readPrec :: ReadPrec DisassociateTrunkInterface
$creadPrec :: ReadPrec DisassociateTrunkInterface
readList :: ReadS [DisassociateTrunkInterface]
$creadList :: ReadS [DisassociateTrunkInterface]
readsPrec :: Int -> ReadS DisassociateTrunkInterface
$creadsPrec :: Int -> ReadS DisassociateTrunkInterface
Prelude.Read, Int -> DisassociateTrunkInterface -> ShowS
[DisassociateTrunkInterface] -> ShowS
DisassociateTrunkInterface -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateTrunkInterface] -> ShowS
$cshowList :: [DisassociateTrunkInterface] -> ShowS
show :: DisassociateTrunkInterface -> String
$cshow :: DisassociateTrunkInterface -> String
showsPrec :: Int -> DisassociateTrunkInterface -> ShowS
$cshowsPrec :: Int -> DisassociateTrunkInterface -> ShowS
Prelude.Show, forall x.
Rep DisassociateTrunkInterface x -> DisassociateTrunkInterface
forall x.
DisassociateTrunkInterface -> Rep DisassociateTrunkInterface x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateTrunkInterface x -> DisassociateTrunkInterface
$cfrom :: forall x.
DisassociateTrunkInterface -> Rep DisassociateTrunkInterface x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateTrunkInterface' 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:
--
-- 'clientToken', 'disassociateTrunkInterface_clientToken' - Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Run_Instance_Idempotency.html How to Ensure Idempotency>.
--
-- 'dryRun', 'disassociateTrunkInterface_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'associationId', 'disassociateTrunkInterface_associationId' - The ID of the association
newDisassociateTrunkInterface ::
  -- | 'associationId'
  Prelude.Text ->
  DisassociateTrunkInterface
newDisassociateTrunkInterface :: Text -> DisassociateTrunkInterface
newDisassociateTrunkInterface Text
pAssociationId_ =
  DisassociateTrunkInterface'
    { $sel:clientToken:DisassociateTrunkInterface' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:DisassociateTrunkInterface' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:associationId:DisassociateTrunkInterface' :: Text
associationId = Text
pAssociationId_
    }

-- | Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Run_Instance_Idempotency.html How to Ensure Idempotency>.
disassociateTrunkInterface_clientToken :: Lens.Lens' DisassociateTrunkInterface (Prelude.Maybe Prelude.Text)
disassociateTrunkInterface_clientToken :: Lens' DisassociateTrunkInterface (Maybe Text)
disassociateTrunkInterface_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateTrunkInterface' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: DisassociateTrunkInterface
s@DisassociateTrunkInterface' {} Maybe Text
a -> DisassociateTrunkInterface
s {$sel:clientToken:DisassociateTrunkInterface' :: Maybe Text
clientToken = Maybe Text
a} :: DisassociateTrunkInterface)

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
disassociateTrunkInterface_dryRun :: Lens.Lens' DisassociateTrunkInterface (Prelude.Maybe Prelude.Bool)
disassociateTrunkInterface_dryRun :: Lens' DisassociateTrunkInterface (Maybe Bool)
disassociateTrunkInterface_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateTrunkInterface' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DisassociateTrunkInterface
s@DisassociateTrunkInterface' {} Maybe Bool
a -> DisassociateTrunkInterface
s {$sel:dryRun:DisassociateTrunkInterface' :: Maybe Bool
dryRun = Maybe Bool
a} :: DisassociateTrunkInterface)

-- | The ID of the association
disassociateTrunkInterface_associationId :: Lens.Lens' DisassociateTrunkInterface Prelude.Text
disassociateTrunkInterface_associationId :: Lens' DisassociateTrunkInterface Text
disassociateTrunkInterface_associationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateTrunkInterface' {Text
associationId :: Text
$sel:associationId:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Text
associationId} -> Text
associationId) (\s :: DisassociateTrunkInterface
s@DisassociateTrunkInterface' {} Text
a -> DisassociateTrunkInterface
s {$sel:associationId:DisassociateTrunkInterface' :: Text
associationId = Text
a} :: DisassociateTrunkInterface)

instance Core.AWSRequest DisassociateTrunkInterface where
  type
    AWSResponse DisassociateTrunkInterface =
      DisassociateTrunkInterfaceResponse
  request :: (Service -> Service)
-> DisassociateTrunkInterface -> Request DisassociateTrunkInterface
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DisassociateTrunkInterface
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisassociateTrunkInterface)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe Bool -> Int -> DisassociateTrunkInterfaceResponse
DisassociateTrunkInterfaceResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"clientToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"return")
            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 DisassociateTrunkInterface where
  hashWithSalt :: Int -> DisassociateTrunkInterface -> Int
hashWithSalt Int
_salt DisassociateTrunkInterface' {Maybe Bool
Maybe Text
Text
associationId :: Text
dryRun :: Maybe Bool
clientToken :: Maybe Text
$sel:associationId:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Text
$sel:dryRun:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Maybe Bool
$sel:clientToken:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
associationId

instance Prelude.NFData DisassociateTrunkInterface where
  rnf :: DisassociateTrunkInterface -> ()
rnf DisassociateTrunkInterface' {Maybe Bool
Maybe Text
Text
associationId :: Text
dryRun :: Maybe Bool
clientToken :: Maybe Text
$sel:associationId:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Text
$sel:dryRun:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Maybe Bool
$sel:clientToken:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
associationId

instance Data.ToHeaders DisassociateTrunkInterface where
  toHeaders :: DisassociateTrunkInterface -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DisassociateTrunkInterface where
  toQuery :: DisassociateTrunkInterface -> QueryString
toQuery DisassociateTrunkInterface' {Maybe Bool
Maybe Text
Text
associationId :: Text
dryRun :: Maybe Bool
clientToken :: Maybe Text
$sel:associationId:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Text
$sel:dryRun:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Maybe Bool
$sel:clientToken:DisassociateTrunkInterface' :: DisassociateTrunkInterface -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DisassociateTrunkInterface" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"ClientToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
clientToken,
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"AssociationId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
associationId
      ]

-- | /See:/ 'newDisassociateTrunkInterfaceResponse' smart constructor.
data DisassociateTrunkInterfaceResponse = DisassociateTrunkInterfaceResponse'
  { -- | Unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request. For more information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Run_Instance_Idempotency.html How to Ensure Idempotency>.
    DisassociateTrunkInterfaceResponse -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | Returns @true@ if the request succeeds; otherwise, it returns an error.
    DisassociateTrunkInterfaceResponse -> Maybe Bool
return' :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    DisassociateTrunkInterfaceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DisassociateTrunkInterfaceResponse
-> DisassociateTrunkInterfaceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateTrunkInterfaceResponse
-> DisassociateTrunkInterfaceResponse -> Bool
$c/= :: DisassociateTrunkInterfaceResponse
-> DisassociateTrunkInterfaceResponse -> Bool
== :: DisassociateTrunkInterfaceResponse
-> DisassociateTrunkInterfaceResponse -> Bool
$c== :: DisassociateTrunkInterfaceResponse
-> DisassociateTrunkInterfaceResponse -> Bool
Prelude.Eq, ReadPrec [DisassociateTrunkInterfaceResponse]
ReadPrec DisassociateTrunkInterfaceResponse
Int -> ReadS DisassociateTrunkInterfaceResponse
ReadS [DisassociateTrunkInterfaceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateTrunkInterfaceResponse]
$creadListPrec :: ReadPrec [DisassociateTrunkInterfaceResponse]
readPrec :: ReadPrec DisassociateTrunkInterfaceResponse
$creadPrec :: ReadPrec DisassociateTrunkInterfaceResponse
readList :: ReadS [DisassociateTrunkInterfaceResponse]
$creadList :: ReadS [DisassociateTrunkInterfaceResponse]
readsPrec :: Int -> ReadS DisassociateTrunkInterfaceResponse
$creadsPrec :: Int -> ReadS DisassociateTrunkInterfaceResponse
Prelude.Read, Int -> DisassociateTrunkInterfaceResponse -> ShowS
[DisassociateTrunkInterfaceResponse] -> ShowS
DisassociateTrunkInterfaceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateTrunkInterfaceResponse] -> ShowS
$cshowList :: [DisassociateTrunkInterfaceResponse] -> ShowS
show :: DisassociateTrunkInterfaceResponse -> String
$cshow :: DisassociateTrunkInterfaceResponse -> String
showsPrec :: Int -> DisassociateTrunkInterfaceResponse -> ShowS
$cshowsPrec :: Int -> DisassociateTrunkInterfaceResponse -> ShowS
Prelude.Show, forall x.
Rep DisassociateTrunkInterfaceResponse x
-> DisassociateTrunkInterfaceResponse
forall x.
DisassociateTrunkInterfaceResponse
-> Rep DisassociateTrunkInterfaceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateTrunkInterfaceResponse x
-> DisassociateTrunkInterfaceResponse
$cfrom :: forall x.
DisassociateTrunkInterfaceResponse
-> Rep DisassociateTrunkInterfaceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateTrunkInterfaceResponse' 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:
--
-- 'clientToken', 'disassociateTrunkInterfaceResponse_clientToken' - Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Run_Instance_Idempotency.html How to Ensure Idempotency>.
--
-- 'return'', 'disassociateTrunkInterfaceResponse_return' - Returns @true@ if the request succeeds; otherwise, it returns an error.
--
-- 'httpStatus', 'disassociateTrunkInterfaceResponse_httpStatus' - The response's http status code.
newDisassociateTrunkInterfaceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisassociateTrunkInterfaceResponse
newDisassociateTrunkInterfaceResponse :: Int -> DisassociateTrunkInterfaceResponse
newDisassociateTrunkInterfaceResponse Int
pHttpStatus_ =
  DisassociateTrunkInterfaceResponse'
    { $sel:clientToken:DisassociateTrunkInterfaceResponse' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:return':DisassociateTrunkInterfaceResponse' :: Maybe Bool
return' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DisassociateTrunkInterfaceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/Run_Instance_Idempotency.html How to Ensure Idempotency>.
disassociateTrunkInterfaceResponse_clientToken :: Lens.Lens' DisassociateTrunkInterfaceResponse (Prelude.Maybe Prelude.Text)
disassociateTrunkInterfaceResponse_clientToken :: Lens' DisassociateTrunkInterfaceResponse (Maybe Text)
disassociateTrunkInterfaceResponse_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateTrunkInterfaceResponse' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:DisassociateTrunkInterfaceResponse' :: DisassociateTrunkInterfaceResponse -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: DisassociateTrunkInterfaceResponse
s@DisassociateTrunkInterfaceResponse' {} Maybe Text
a -> DisassociateTrunkInterfaceResponse
s {$sel:clientToken:DisassociateTrunkInterfaceResponse' :: Maybe Text
clientToken = Maybe Text
a} :: DisassociateTrunkInterfaceResponse)

-- | Returns @true@ if the request succeeds; otherwise, it returns an error.
disassociateTrunkInterfaceResponse_return :: Lens.Lens' DisassociateTrunkInterfaceResponse (Prelude.Maybe Prelude.Bool)
disassociateTrunkInterfaceResponse_return :: Lens' DisassociateTrunkInterfaceResponse (Maybe Bool)
disassociateTrunkInterfaceResponse_return = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateTrunkInterfaceResponse' {Maybe Bool
return' :: Maybe Bool
$sel:return':DisassociateTrunkInterfaceResponse' :: DisassociateTrunkInterfaceResponse -> Maybe Bool
return'} -> Maybe Bool
return') (\s :: DisassociateTrunkInterfaceResponse
s@DisassociateTrunkInterfaceResponse' {} Maybe Bool
a -> DisassociateTrunkInterfaceResponse
s {$sel:return':DisassociateTrunkInterfaceResponse' :: Maybe Bool
return' = Maybe Bool
a} :: DisassociateTrunkInterfaceResponse)

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

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