{-# 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.GetFlowLogsIntegrationTemplate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Generates a CloudFormation template that streamlines and automates the
-- integration of VPC flow logs with Amazon Athena. This make it easier for
-- you to query and gain insights from VPC flow logs data. Based on the
-- information that you provide, we configure resources in the template to
-- do the following:
--
-- -   Create a table in Athena that maps fields to a custom log format
--
-- -   Create a Lambda function that updates the table with new partitions
--     on a daily, weekly, or monthly basis
--
-- -   Create a table partitioned between two timestamps in the past
--
-- -   Create a set of named queries in Athena that you can use to get
--     started quickly
module Amazonka.EC2.GetFlowLogsIntegrationTemplate
  ( -- * Creating a Request
    GetFlowLogsIntegrationTemplate (..),
    newGetFlowLogsIntegrationTemplate,

    -- * Request Lenses
    getFlowLogsIntegrationTemplate_dryRun,
    getFlowLogsIntegrationTemplate_flowLogId,
    getFlowLogsIntegrationTemplate_configDeliveryS3DestinationArn,
    getFlowLogsIntegrationTemplate_integrateServices,

    -- * Destructuring the Response
    GetFlowLogsIntegrationTemplateResponse (..),
    newGetFlowLogsIntegrationTemplateResponse,

    -- * Response Lenses
    getFlowLogsIntegrationTemplateResponse_result,
    getFlowLogsIntegrationTemplateResponse_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:/ 'newGetFlowLogsIntegrationTemplate' smart constructor.
data GetFlowLogsIntegrationTemplate = GetFlowLogsIntegrationTemplate'
  { -- | 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@.
    GetFlowLogsIntegrationTemplate -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the flow log.
    GetFlowLogsIntegrationTemplate -> Text
flowLogId :: Prelude.Text,
    -- | To store the CloudFormation template in Amazon S3, specify the location
    -- in Amazon S3.
    GetFlowLogsIntegrationTemplate -> Text
configDeliveryS3DestinationArn :: Prelude.Text,
    -- | Information about the service integration.
    GetFlowLogsIntegrationTemplate -> IntegrateServices
integrateServices :: IntegrateServices
  }
  deriving (GetFlowLogsIntegrationTemplate
-> GetFlowLogsIntegrationTemplate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFlowLogsIntegrationTemplate
-> GetFlowLogsIntegrationTemplate -> Bool
$c/= :: GetFlowLogsIntegrationTemplate
-> GetFlowLogsIntegrationTemplate -> Bool
== :: GetFlowLogsIntegrationTemplate
-> GetFlowLogsIntegrationTemplate -> Bool
$c== :: GetFlowLogsIntegrationTemplate
-> GetFlowLogsIntegrationTemplate -> Bool
Prelude.Eq, ReadPrec [GetFlowLogsIntegrationTemplate]
ReadPrec GetFlowLogsIntegrationTemplate
Int -> ReadS GetFlowLogsIntegrationTemplate
ReadS [GetFlowLogsIntegrationTemplate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFlowLogsIntegrationTemplate]
$creadListPrec :: ReadPrec [GetFlowLogsIntegrationTemplate]
readPrec :: ReadPrec GetFlowLogsIntegrationTemplate
$creadPrec :: ReadPrec GetFlowLogsIntegrationTemplate
readList :: ReadS [GetFlowLogsIntegrationTemplate]
$creadList :: ReadS [GetFlowLogsIntegrationTemplate]
readsPrec :: Int -> ReadS GetFlowLogsIntegrationTemplate
$creadsPrec :: Int -> ReadS GetFlowLogsIntegrationTemplate
Prelude.Read, Int -> GetFlowLogsIntegrationTemplate -> ShowS
[GetFlowLogsIntegrationTemplate] -> ShowS
GetFlowLogsIntegrationTemplate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFlowLogsIntegrationTemplate] -> ShowS
$cshowList :: [GetFlowLogsIntegrationTemplate] -> ShowS
show :: GetFlowLogsIntegrationTemplate -> String
$cshow :: GetFlowLogsIntegrationTemplate -> String
showsPrec :: Int -> GetFlowLogsIntegrationTemplate -> ShowS
$cshowsPrec :: Int -> GetFlowLogsIntegrationTemplate -> ShowS
Prelude.Show, forall x.
Rep GetFlowLogsIntegrationTemplate x
-> GetFlowLogsIntegrationTemplate
forall x.
GetFlowLogsIntegrationTemplate
-> Rep GetFlowLogsIntegrationTemplate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetFlowLogsIntegrationTemplate x
-> GetFlowLogsIntegrationTemplate
$cfrom :: forall x.
GetFlowLogsIntegrationTemplate
-> Rep GetFlowLogsIntegrationTemplate x
Prelude.Generic)

-- |
-- Create a value of 'GetFlowLogsIntegrationTemplate' 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:
--
-- 'dryRun', 'getFlowLogsIntegrationTemplate_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@.
--
-- 'flowLogId', 'getFlowLogsIntegrationTemplate_flowLogId' - The ID of the flow log.
--
-- 'configDeliveryS3DestinationArn', 'getFlowLogsIntegrationTemplate_configDeliveryS3DestinationArn' - To store the CloudFormation template in Amazon S3, specify the location
-- in Amazon S3.
--
-- 'integrateServices', 'getFlowLogsIntegrationTemplate_integrateServices' - Information about the service integration.
newGetFlowLogsIntegrationTemplate ::
  -- | 'flowLogId'
  Prelude.Text ->
  -- | 'configDeliveryS3DestinationArn'
  Prelude.Text ->
  -- | 'integrateServices'
  IntegrateServices ->
  GetFlowLogsIntegrationTemplate
newGetFlowLogsIntegrationTemplate :: Text -> Text -> IntegrateServices -> GetFlowLogsIntegrationTemplate
newGetFlowLogsIntegrationTemplate
  Text
pFlowLogId_
  Text
pConfigDeliveryS3DestinationArn_
  IntegrateServices
pIntegrateServices_ =
    GetFlowLogsIntegrationTemplate'
      { $sel:dryRun:GetFlowLogsIntegrationTemplate' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:flowLogId:GetFlowLogsIntegrationTemplate' :: Text
flowLogId = Text
pFlowLogId_,
        $sel:configDeliveryS3DestinationArn:GetFlowLogsIntegrationTemplate' :: Text
configDeliveryS3DestinationArn =
          Text
pConfigDeliveryS3DestinationArn_,
        $sel:integrateServices:GetFlowLogsIntegrationTemplate' :: IntegrateServices
integrateServices = IntegrateServices
pIntegrateServices_
      }

-- | 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@.
getFlowLogsIntegrationTemplate_dryRun :: Lens.Lens' GetFlowLogsIntegrationTemplate (Prelude.Maybe Prelude.Bool)
getFlowLogsIntegrationTemplate_dryRun :: Lens' GetFlowLogsIntegrationTemplate (Maybe Bool)
getFlowLogsIntegrationTemplate_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFlowLogsIntegrationTemplate' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: GetFlowLogsIntegrationTemplate
s@GetFlowLogsIntegrationTemplate' {} Maybe Bool
a -> GetFlowLogsIntegrationTemplate
s {$sel:dryRun:GetFlowLogsIntegrationTemplate' :: Maybe Bool
dryRun = Maybe Bool
a} :: GetFlowLogsIntegrationTemplate)

-- | The ID of the flow log.
getFlowLogsIntegrationTemplate_flowLogId :: Lens.Lens' GetFlowLogsIntegrationTemplate Prelude.Text
getFlowLogsIntegrationTemplate_flowLogId :: Lens' GetFlowLogsIntegrationTemplate Text
getFlowLogsIntegrationTemplate_flowLogId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFlowLogsIntegrationTemplate' {Text
flowLogId :: Text
$sel:flowLogId:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Text
flowLogId} -> Text
flowLogId) (\s :: GetFlowLogsIntegrationTemplate
s@GetFlowLogsIntegrationTemplate' {} Text
a -> GetFlowLogsIntegrationTemplate
s {$sel:flowLogId:GetFlowLogsIntegrationTemplate' :: Text
flowLogId = Text
a} :: GetFlowLogsIntegrationTemplate)

-- | To store the CloudFormation template in Amazon S3, specify the location
-- in Amazon S3.
getFlowLogsIntegrationTemplate_configDeliveryS3DestinationArn :: Lens.Lens' GetFlowLogsIntegrationTemplate Prelude.Text
getFlowLogsIntegrationTemplate_configDeliveryS3DestinationArn :: Lens' GetFlowLogsIntegrationTemplate Text
getFlowLogsIntegrationTemplate_configDeliveryS3DestinationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFlowLogsIntegrationTemplate' {Text
configDeliveryS3DestinationArn :: Text
$sel:configDeliveryS3DestinationArn:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Text
configDeliveryS3DestinationArn} -> Text
configDeliveryS3DestinationArn) (\s :: GetFlowLogsIntegrationTemplate
s@GetFlowLogsIntegrationTemplate' {} Text
a -> GetFlowLogsIntegrationTemplate
s {$sel:configDeliveryS3DestinationArn:GetFlowLogsIntegrationTemplate' :: Text
configDeliveryS3DestinationArn = Text
a} :: GetFlowLogsIntegrationTemplate)

-- | Information about the service integration.
getFlowLogsIntegrationTemplate_integrateServices :: Lens.Lens' GetFlowLogsIntegrationTemplate IntegrateServices
getFlowLogsIntegrationTemplate_integrateServices :: Lens' GetFlowLogsIntegrationTemplate IntegrateServices
getFlowLogsIntegrationTemplate_integrateServices = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFlowLogsIntegrationTemplate' {IntegrateServices
integrateServices :: IntegrateServices
$sel:integrateServices:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> IntegrateServices
integrateServices} -> IntegrateServices
integrateServices) (\s :: GetFlowLogsIntegrationTemplate
s@GetFlowLogsIntegrationTemplate' {} IntegrateServices
a -> GetFlowLogsIntegrationTemplate
s {$sel:integrateServices:GetFlowLogsIntegrationTemplate' :: IntegrateServices
integrateServices = IntegrateServices
a} :: GetFlowLogsIntegrationTemplate)

instance
  Core.AWSRequest
    GetFlowLogsIntegrationTemplate
  where
  type
    AWSResponse GetFlowLogsIntegrationTemplate =
      GetFlowLogsIntegrationTemplateResponse
  request :: (Service -> Service)
-> GetFlowLogsIntegrationTemplate
-> Request GetFlowLogsIntegrationTemplate
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 GetFlowLogsIntegrationTemplate
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetFlowLogsIntegrationTemplate)))
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 -> Int -> GetFlowLogsIntegrationTemplateResponse
GetFlowLogsIntegrationTemplateResponse'
            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
"result")
            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
    GetFlowLogsIntegrationTemplate
  where
  hashWithSalt :: Int -> GetFlowLogsIntegrationTemplate -> Int
hashWithSalt
    Int
_salt
    GetFlowLogsIntegrationTemplate' {Maybe Bool
Text
IntegrateServices
integrateServices :: IntegrateServices
configDeliveryS3DestinationArn :: Text
flowLogId :: Text
dryRun :: Maybe Bool
$sel:integrateServices:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> IntegrateServices
$sel:configDeliveryS3DestinationArn:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Text
$sel:flowLogId:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Text
$sel:dryRun:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Maybe Bool
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
flowLogId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configDeliveryS3DestinationArn
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` IntegrateServices
integrateServices

instance
  Prelude.NFData
    GetFlowLogsIntegrationTemplate
  where
  rnf :: GetFlowLogsIntegrationTemplate -> ()
rnf GetFlowLogsIntegrationTemplate' {Maybe Bool
Text
IntegrateServices
integrateServices :: IntegrateServices
configDeliveryS3DestinationArn :: Text
flowLogId :: Text
dryRun :: Maybe Bool
$sel:integrateServices:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> IntegrateServices
$sel:configDeliveryS3DestinationArn:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Text
$sel:flowLogId:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Text
$sel:dryRun:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Maybe Bool
..} =
    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
flowLogId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
configDeliveryS3DestinationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf IntegrateServices
integrateServices

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

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

instance Data.ToQuery GetFlowLogsIntegrationTemplate where
  toQuery :: GetFlowLogsIntegrationTemplate -> QueryString
toQuery GetFlowLogsIntegrationTemplate' {Maybe Bool
Text
IntegrateServices
integrateServices :: IntegrateServices
configDeliveryS3DestinationArn :: Text
flowLogId :: Text
dryRun :: Maybe Bool
$sel:integrateServices:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> IntegrateServices
$sel:configDeliveryS3DestinationArn:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Text
$sel:flowLogId:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Text
$sel:dryRun:GetFlowLogsIntegrationTemplate' :: GetFlowLogsIntegrationTemplate -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"GetFlowLogsIntegrationTemplate" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"FlowLogId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
flowLogId,
        ByteString
"ConfigDeliveryS3DestinationArn"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
configDeliveryS3DestinationArn,
        ByteString
"IntegrateService" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: IntegrateServices
integrateServices
      ]

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

-- |
-- Create a value of 'GetFlowLogsIntegrationTemplateResponse' 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:
--
-- 'result', 'getFlowLogsIntegrationTemplateResponse_result' - The generated CloudFormation template.
--
-- 'httpStatus', 'getFlowLogsIntegrationTemplateResponse_httpStatus' - The response's http status code.
newGetFlowLogsIntegrationTemplateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetFlowLogsIntegrationTemplateResponse
newGetFlowLogsIntegrationTemplateResponse :: Int -> GetFlowLogsIntegrationTemplateResponse
newGetFlowLogsIntegrationTemplateResponse
  Int
pHttpStatus_ =
    GetFlowLogsIntegrationTemplateResponse'
      { $sel:result:GetFlowLogsIntegrationTemplateResponse' :: Maybe Text
result =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetFlowLogsIntegrationTemplateResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The generated CloudFormation template.
getFlowLogsIntegrationTemplateResponse_result :: Lens.Lens' GetFlowLogsIntegrationTemplateResponse (Prelude.Maybe Prelude.Text)
getFlowLogsIntegrationTemplateResponse_result :: Lens' GetFlowLogsIntegrationTemplateResponse (Maybe Text)
getFlowLogsIntegrationTemplateResponse_result = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFlowLogsIntegrationTemplateResponse' {Maybe Text
result :: Maybe Text
$sel:result:GetFlowLogsIntegrationTemplateResponse' :: GetFlowLogsIntegrationTemplateResponse -> Maybe Text
result} -> Maybe Text
result) (\s :: GetFlowLogsIntegrationTemplateResponse
s@GetFlowLogsIntegrationTemplateResponse' {} Maybe Text
a -> GetFlowLogsIntegrationTemplateResponse
s {$sel:result:GetFlowLogsIntegrationTemplateResponse' :: Maybe Text
result = Maybe Text
a} :: GetFlowLogsIntegrationTemplateResponse)

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

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