{-# 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.MediaConnect.AddFlowVpcInterfaces
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds VPC interfaces to flow
module Amazonka.MediaConnect.AddFlowVpcInterfaces
  ( -- * Creating a Request
    AddFlowVpcInterfaces (..),
    newAddFlowVpcInterfaces,

    -- * Request Lenses
    addFlowVpcInterfaces_flowArn,
    addFlowVpcInterfaces_vpcInterfaces,

    -- * Destructuring the Response
    AddFlowVpcInterfacesResponse (..),
    newAddFlowVpcInterfacesResponse,

    -- * Response Lenses
    addFlowVpcInterfacesResponse_flowArn,
    addFlowVpcInterfacesResponse_vpcInterfaces,
    addFlowVpcInterfacesResponse_httpStatus,
  )
where

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

-- | A request to add VPC interfaces to the flow.
--
-- /See:/ 'newAddFlowVpcInterfaces' smart constructor.
data AddFlowVpcInterfaces = AddFlowVpcInterfaces'
  { -- | The flow that you want to mutate.
    AddFlowVpcInterfaces -> Text
flowArn :: Prelude.Text,
    -- | A list of VPC interfaces that you want to add.
    AddFlowVpcInterfaces -> [VpcInterfaceRequest]
vpcInterfaces :: [VpcInterfaceRequest]
  }
  deriving (AddFlowVpcInterfaces -> AddFlowVpcInterfaces -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddFlowVpcInterfaces -> AddFlowVpcInterfaces -> Bool
$c/= :: AddFlowVpcInterfaces -> AddFlowVpcInterfaces -> Bool
== :: AddFlowVpcInterfaces -> AddFlowVpcInterfaces -> Bool
$c== :: AddFlowVpcInterfaces -> AddFlowVpcInterfaces -> Bool
Prelude.Eq, ReadPrec [AddFlowVpcInterfaces]
ReadPrec AddFlowVpcInterfaces
Int -> ReadS AddFlowVpcInterfaces
ReadS [AddFlowVpcInterfaces]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddFlowVpcInterfaces]
$creadListPrec :: ReadPrec [AddFlowVpcInterfaces]
readPrec :: ReadPrec AddFlowVpcInterfaces
$creadPrec :: ReadPrec AddFlowVpcInterfaces
readList :: ReadS [AddFlowVpcInterfaces]
$creadList :: ReadS [AddFlowVpcInterfaces]
readsPrec :: Int -> ReadS AddFlowVpcInterfaces
$creadsPrec :: Int -> ReadS AddFlowVpcInterfaces
Prelude.Read, Int -> AddFlowVpcInterfaces -> ShowS
[AddFlowVpcInterfaces] -> ShowS
AddFlowVpcInterfaces -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddFlowVpcInterfaces] -> ShowS
$cshowList :: [AddFlowVpcInterfaces] -> ShowS
show :: AddFlowVpcInterfaces -> String
$cshow :: AddFlowVpcInterfaces -> String
showsPrec :: Int -> AddFlowVpcInterfaces -> ShowS
$cshowsPrec :: Int -> AddFlowVpcInterfaces -> ShowS
Prelude.Show, forall x. Rep AddFlowVpcInterfaces x -> AddFlowVpcInterfaces
forall x. AddFlowVpcInterfaces -> Rep AddFlowVpcInterfaces x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddFlowVpcInterfaces x -> AddFlowVpcInterfaces
$cfrom :: forall x. AddFlowVpcInterfaces -> Rep AddFlowVpcInterfaces x
Prelude.Generic)

-- |
-- Create a value of 'AddFlowVpcInterfaces' 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:
--
-- 'flowArn', 'addFlowVpcInterfaces_flowArn' - The flow that you want to mutate.
--
-- 'vpcInterfaces', 'addFlowVpcInterfaces_vpcInterfaces' - A list of VPC interfaces that you want to add.
newAddFlowVpcInterfaces ::
  -- | 'flowArn'
  Prelude.Text ->
  AddFlowVpcInterfaces
newAddFlowVpcInterfaces :: Text -> AddFlowVpcInterfaces
newAddFlowVpcInterfaces Text
pFlowArn_ =
  AddFlowVpcInterfaces'
    { $sel:flowArn:AddFlowVpcInterfaces' :: Text
flowArn = Text
pFlowArn_,
      $sel:vpcInterfaces:AddFlowVpcInterfaces' :: [VpcInterfaceRequest]
vpcInterfaces = forall a. Monoid a => a
Prelude.mempty
    }

-- | The flow that you want to mutate.
addFlowVpcInterfaces_flowArn :: Lens.Lens' AddFlowVpcInterfaces Prelude.Text
addFlowVpcInterfaces_flowArn :: Lens' AddFlowVpcInterfaces Text
addFlowVpcInterfaces_flowArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddFlowVpcInterfaces' {Text
flowArn :: Text
$sel:flowArn:AddFlowVpcInterfaces' :: AddFlowVpcInterfaces -> Text
flowArn} -> Text
flowArn) (\s :: AddFlowVpcInterfaces
s@AddFlowVpcInterfaces' {} Text
a -> AddFlowVpcInterfaces
s {$sel:flowArn:AddFlowVpcInterfaces' :: Text
flowArn = Text
a} :: AddFlowVpcInterfaces)

-- | A list of VPC interfaces that you want to add.
addFlowVpcInterfaces_vpcInterfaces :: Lens.Lens' AddFlowVpcInterfaces [VpcInterfaceRequest]
addFlowVpcInterfaces_vpcInterfaces :: Lens' AddFlowVpcInterfaces [VpcInterfaceRequest]
addFlowVpcInterfaces_vpcInterfaces = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddFlowVpcInterfaces' {[VpcInterfaceRequest]
vpcInterfaces :: [VpcInterfaceRequest]
$sel:vpcInterfaces:AddFlowVpcInterfaces' :: AddFlowVpcInterfaces -> [VpcInterfaceRequest]
vpcInterfaces} -> [VpcInterfaceRequest]
vpcInterfaces) (\s :: AddFlowVpcInterfaces
s@AddFlowVpcInterfaces' {} [VpcInterfaceRequest]
a -> AddFlowVpcInterfaces
s {$sel:vpcInterfaces:AddFlowVpcInterfaces' :: [VpcInterfaceRequest]
vpcInterfaces = [VpcInterfaceRequest]
a} :: AddFlowVpcInterfaces) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest AddFlowVpcInterfaces where
  type
    AWSResponse AddFlowVpcInterfaces =
      AddFlowVpcInterfacesResponse
  request :: (Service -> Service)
-> AddFlowVpcInterfaces -> Request AddFlowVpcInterfaces
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 AddFlowVpcInterfaces
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AddFlowVpcInterfaces)))
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
-> Maybe [VpcInterface] -> Int -> AddFlowVpcInterfacesResponse
AddFlowVpcInterfacesResponse'
            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
"flowArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"vpcInterfaces" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 AddFlowVpcInterfaces where
  hashWithSalt :: Int -> AddFlowVpcInterfaces -> Int
hashWithSalt Int
_salt AddFlowVpcInterfaces' {[VpcInterfaceRequest]
Text
vpcInterfaces :: [VpcInterfaceRequest]
flowArn :: Text
$sel:vpcInterfaces:AddFlowVpcInterfaces' :: AddFlowVpcInterfaces -> [VpcInterfaceRequest]
$sel:flowArn:AddFlowVpcInterfaces' :: AddFlowVpcInterfaces -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
flowArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [VpcInterfaceRequest]
vpcInterfaces

instance Prelude.NFData AddFlowVpcInterfaces where
  rnf :: AddFlowVpcInterfaces -> ()
rnf AddFlowVpcInterfaces' {[VpcInterfaceRequest]
Text
vpcInterfaces :: [VpcInterfaceRequest]
flowArn :: Text
$sel:vpcInterfaces:AddFlowVpcInterfaces' :: AddFlowVpcInterfaces -> [VpcInterfaceRequest]
$sel:flowArn:AddFlowVpcInterfaces' :: AddFlowVpcInterfaces -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
flowArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [VpcInterfaceRequest]
vpcInterfaces

instance Data.ToHeaders AddFlowVpcInterfaces where
  toHeaders :: AddFlowVpcInterfaces -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON AddFlowVpcInterfaces where
  toJSON :: AddFlowVpcInterfaces -> Value
toJSON AddFlowVpcInterfaces' {[VpcInterfaceRequest]
Text
vpcInterfaces :: [VpcInterfaceRequest]
flowArn :: Text
$sel:vpcInterfaces:AddFlowVpcInterfaces' :: AddFlowVpcInterfaces -> [VpcInterfaceRequest]
$sel:flowArn:AddFlowVpcInterfaces' :: AddFlowVpcInterfaces -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"vpcInterfaces" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [VpcInterfaceRequest]
vpcInterfaces)
          ]
      )

instance Data.ToPath AddFlowVpcInterfaces where
  toPath :: AddFlowVpcInterfaces -> ByteString
toPath AddFlowVpcInterfaces' {[VpcInterfaceRequest]
Text
vpcInterfaces :: [VpcInterfaceRequest]
flowArn :: Text
$sel:vpcInterfaces:AddFlowVpcInterfaces' :: AddFlowVpcInterfaces -> [VpcInterfaceRequest]
$sel:flowArn:AddFlowVpcInterfaces' :: AddFlowVpcInterfaces -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/flows/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
flowArn, ByteString
"/vpcInterfaces"]

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

-- | /See:/ 'newAddFlowVpcInterfacesResponse' smart constructor.
data AddFlowVpcInterfacesResponse = AddFlowVpcInterfacesResponse'
  { -- | The ARN of the flow that these VPC interfaces were added to.
    AddFlowVpcInterfacesResponse -> Maybe Text
flowArn :: Prelude.Maybe Prelude.Text,
    -- | The details of the newly added VPC interfaces.
    AddFlowVpcInterfacesResponse -> Maybe [VpcInterface]
vpcInterfaces :: Prelude.Maybe [VpcInterface],
    -- | The response's http status code.
    AddFlowVpcInterfacesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AddFlowVpcInterfacesResponse
-> AddFlowVpcInterfacesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddFlowVpcInterfacesResponse
-> AddFlowVpcInterfacesResponse -> Bool
$c/= :: AddFlowVpcInterfacesResponse
-> AddFlowVpcInterfacesResponse -> Bool
== :: AddFlowVpcInterfacesResponse
-> AddFlowVpcInterfacesResponse -> Bool
$c== :: AddFlowVpcInterfacesResponse
-> AddFlowVpcInterfacesResponse -> Bool
Prelude.Eq, ReadPrec [AddFlowVpcInterfacesResponse]
ReadPrec AddFlowVpcInterfacesResponse
Int -> ReadS AddFlowVpcInterfacesResponse
ReadS [AddFlowVpcInterfacesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddFlowVpcInterfacesResponse]
$creadListPrec :: ReadPrec [AddFlowVpcInterfacesResponse]
readPrec :: ReadPrec AddFlowVpcInterfacesResponse
$creadPrec :: ReadPrec AddFlowVpcInterfacesResponse
readList :: ReadS [AddFlowVpcInterfacesResponse]
$creadList :: ReadS [AddFlowVpcInterfacesResponse]
readsPrec :: Int -> ReadS AddFlowVpcInterfacesResponse
$creadsPrec :: Int -> ReadS AddFlowVpcInterfacesResponse
Prelude.Read, Int -> AddFlowVpcInterfacesResponse -> ShowS
[AddFlowVpcInterfacesResponse] -> ShowS
AddFlowVpcInterfacesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddFlowVpcInterfacesResponse] -> ShowS
$cshowList :: [AddFlowVpcInterfacesResponse] -> ShowS
show :: AddFlowVpcInterfacesResponse -> String
$cshow :: AddFlowVpcInterfacesResponse -> String
showsPrec :: Int -> AddFlowVpcInterfacesResponse -> ShowS
$cshowsPrec :: Int -> AddFlowVpcInterfacesResponse -> ShowS
Prelude.Show, forall x.
Rep AddFlowVpcInterfacesResponse x -> AddFlowVpcInterfacesResponse
forall x.
AddFlowVpcInterfacesResponse -> Rep AddFlowVpcInterfacesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AddFlowVpcInterfacesResponse x -> AddFlowVpcInterfacesResponse
$cfrom :: forall x.
AddFlowVpcInterfacesResponse -> Rep AddFlowVpcInterfacesResponse x
Prelude.Generic)

-- |
-- Create a value of 'AddFlowVpcInterfacesResponse' 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:
--
-- 'flowArn', 'addFlowVpcInterfacesResponse_flowArn' - The ARN of the flow that these VPC interfaces were added to.
--
-- 'vpcInterfaces', 'addFlowVpcInterfacesResponse_vpcInterfaces' - The details of the newly added VPC interfaces.
--
-- 'httpStatus', 'addFlowVpcInterfacesResponse_httpStatus' - The response's http status code.
newAddFlowVpcInterfacesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AddFlowVpcInterfacesResponse
newAddFlowVpcInterfacesResponse :: Int -> AddFlowVpcInterfacesResponse
newAddFlowVpcInterfacesResponse Int
pHttpStatus_ =
  AddFlowVpcInterfacesResponse'
    { $sel:flowArn:AddFlowVpcInterfacesResponse' :: Maybe Text
flowArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:vpcInterfaces:AddFlowVpcInterfacesResponse' :: Maybe [VpcInterface]
vpcInterfaces = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AddFlowVpcInterfacesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the flow that these VPC interfaces were added to.
addFlowVpcInterfacesResponse_flowArn :: Lens.Lens' AddFlowVpcInterfacesResponse (Prelude.Maybe Prelude.Text)
addFlowVpcInterfacesResponse_flowArn :: Lens' AddFlowVpcInterfacesResponse (Maybe Text)
addFlowVpcInterfacesResponse_flowArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddFlowVpcInterfacesResponse' {Maybe Text
flowArn :: Maybe Text
$sel:flowArn:AddFlowVpcInterfacesResponse' :: AddFlowVpcInterfacesResponse -> Maybe Text
flowArn} -> Maybe Text
flowArn) (\s :: AddFlowVpcInterfacesResponse
s@AddFlowVpcInterfacesResponse' {} Maybe Text
a -> AddFlowVpcInterfacesResponse
s {$sel:flowArn:AddFlowVpcInterfacesResponse' :: Maybe Text
flowArn = Maybe Text
a} :: AddFlowVpcInterfacesResponse)

-- | The details of the newly added VPC interfaces.
addFlowVpcInterfacesResponse_vpcInterfaces :: Lens.Lens' AddFlowVpcInterfacesResponse (Prelude.Maybe [VpcInterface])
addFlowVpcInterfacesResponse_vpcInterfaces :: Lens' AddFlowVpcInterfacesResponse (Maybe [VpcInterface])
addFlowVpcInterfacesResponse_vpcInterfaces = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddFlowVpcInterfacesResponse' {Maybe [VpcInterface]
vpcInterfaces :: Maybe [VpcInterface]
$sel:vpcInterfaces:AddFlowVpcInterfacesResponse' :: AddFlowVpcInterfacesResponse -> Maybe [VpcInterface]
vpcInterfaces} -> Maybe [VpcInterface]
vpcInterfaces) (\s :: AddFlowVpcInterfacesResponse
s@AddFlowVpcInterfacesResponse' {} Maybe [VpcInterface]
a -> AddFlowVpcInterfacesResponse
s {$sel:vpcInterfaces:AddFlowVpcInterfacesResponse' :: Maybe [VpcInterface]
vpcInterfaces = Maybe [VpcInterface]
a} :: AddFlowVpcInterfacesResponse) 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 response's http status code.
addFlowVpcInterfacesResponse_httpStatus :: Lens.Lens' AddFlowVpcInterfacesResponse Prelude.Int
addFlowVpcInterfacesResponse_httpStatus :: Lens' AddFlowVpcInterfacesResponse Int
addFlowVpcInterfacesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddFlowVpcInterfacesResponse' {Int
httpStatus :: Int
$sel:httpStatus:AddFlowVpcInterfacesResponse' :: AddFlowVpcInterfacesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AddFlowVpcInterfacesResponse
s@AddFlowVpcInterfacesResponse' {} Int
a -> AddFlowVpcInterfacesResponse
s {$sel:httpStatus:AddFlowVpcInterfacesResponse' :: Int
httpStatus = Int
a} :: AddFlowVpcInterfacesResponse)

instance Prelude.NFData AddFlowVpcInterfacesResponse where
  rnf :: AddFlowVpcInterfacesResponse -> ()
rnf AddFlowVpcInterfacesResponse' {Int
Maybe [VpcInterface]
Maybe Text
httpStatus :: Int
vpcInterfaces :: Maybe [VpcInterface]
flowArn :: Maybe Text
$sel:httpStatus:AddFlowVpcInterfacesResponse' :: AddFlowVpcInterfacesResponse -> Int
$sel:vpcInterfaces:AddFlowVpcInterfacesResponse' :: AddFlowVpcInterfacesResponse -> Maybe [VpcInterface]
$sel:flowArn:AddFlowVpcInterfacesResponse' :: AddFlowVpcInterfacesResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
flowArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [VpcInterface]
vpcInterfaces
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus