{-# 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.RestoreManagedPrefixListVersion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Restores the entries from a previous version of a managed prefix list to
-- a new version of the prefix list.
module Amazonka.EC2.RestoreManagedPrefixListVersion
  ( -- * Creating a Request
    RestoreManagedPrefixListVersion (..),
    newRestoreManagedPrefixListVersion,

    -- * Request Lenses
    restoreManagedPrefixListVersion_dryRun,
    restoreManagedPrefixListVersion_prefixListId,
    restoreManagedPrefixListVersion_previousVersion,
    restoreManagedPrefixListVersion_currentVersion,

    -- * Destructuring the Response
    RestoreManagedPrefixListVersionResponse (..),
    newRestoreManagedPrefixListVersionResponse,

    -- * Response Lenses
    restoreManagedPrefixListVersionResponse_prefixList,
    restoreManagedPrefixListVersionResponse_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:/ 'newRestoreManagedPrefixListVersion' smart constructor.
data RestoreManagedPrefixListVersion = RestoreManagedPrefixListVersion'
  { -- | 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@.
    RestoreManagedPrefixListVersion -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the prefix list.
    RestoreManagedPrefixListVersion -> Text
prefixListId :: Prelude.Text,
    -- | The version to restore.
    RestoreManagedPrefixListVersion -> Integer
previousVersion :: Prelude.Integer,
    -- | The current version number for the prefix list.
    RestoreManagedPrefixListVersion -> Integer
currentVersion :: Prelude.Integer
  }
  deriving (RestoreManagedPrefixListVersion
-> RestoreManagedPrefixListVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreManagedPrefixListVersion
-> RestoreManagedPrefixListVersion -> Bool
$c/= :: RestoreManagedPrefixListVersion
-> RestoreManagedPrefixListVersion -> Bool
== :: RestoreManagedPrefixListVersion
-> RestoreManagedPrefixListVersion -> Bool
$c== :: RestoreManagedPrefixListVersion
-> RestoreManagedPrefixListVersion -> Bool
Prelude.Eq, ReadPrec [RestoreManagedPrefixListVersion]
ReadPrec RestoreManagedPrefixListVersion
Int -> ReadS RestoreManagedPrefixListVersion
ReadS [RestoreManagedPrefixListVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreManagedPrefixListVersion]
$creadListPrec :: ReadPrec [RestoreManagedPrefixListVersion]
readPrec :: ReadPrec RestoreManagedPrefixListVersion
$creadPrec :: ReadPrec RestoreManagedPrefixListVersion
readList :: ReadS [RestoreManagedPrefixListVersion]
$creadList :: ReadS [RestoreManagedPrefixListVersion]
readsPrec :: Int -> ReadS RestoreManagedPrefixListVersion
$creadsPrec :: Int -> ReadS RestoreManagedPrefixListVersion
Prelude.Read, Int -> RestoreManagedPrefixListVersion -> ShowS
[RestoreManagedPrefixListVersion] -> ShowS
RestoreManagedPrefixListVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreManagedPrefixListVersion] -> ShowS
$cshowList :: [RestoreManagedPrefixListVersion] -> ShowS
show :: RestoreManagedPrefixListVersion -> String
$cshow :: RestoreManagedPrefixListVersion -> String
showsPrec :: Int -> RestoreManagedPrefixListVersion -> ShowS
$cshowsPrec :: Int -> RestoreManagedPrefixListVersion -> ShowS
Prelude.Show, forall x.
Rep RestoreManagedPrefixListVersion x
-> RestoreManagedPrefixListVersion
forall x.
RestoreManagedPrefixListVersion
-> Rep RestoreManagedPrefixListVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RestoreManagedPrefixListVersion x
-> RestoreManagedPrefixListVersion
$cfrom :: forall x.
RestoreManagedPrefixListVersion
-> Rep RestoreManagedPrefixListVersion x
Prelude.Generic)

-- |
-- Create a value of 'RestoreManagedPrefixListVersion' 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', 'restoreManagedPrefixListVersion_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@.
--
-- 'prefixListId', 'restoreManagedPrefixListVersion_prefixListId' - The ID of the prefix list.
--
-- 'previousVersion', 'restoreManagedPrefixListVersion_previousVersion' - The version to restore.
--
-- 'currentVersion', 'restoreManagedPrefixListVersion_currentVersion' - The current version number for the prefix list.
newRestoreManagedPrefixListVersion ::
  -- | 'prefixListId'
  Prelude.Text ->
  -- | 'previousVersion'
  Prelude.Integer ->
  -- | 'currentVersion'
  Prelude.Integer ->
  RestoreManagedPrefixListVersion
newRestoreManagedPrefixListVersion :: Text -> Integer -> Integer -> RestoreManagedPrefixListVersion
newRestoreManagedPrefixListVersion
  Text
pPrefixListId_
  Integer
pPreviousVersion_
  Integer
pCurrentVersion_ =
    RestoreManagedPrefixListVersion'
      { $sel:dryRun:RestoreManagedPrefixListVersion' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:prefixListId:RestoreManagedPrefixListVersion' :: Text
prefixListId = Text
pPrefixListId_,
        $sel:previousVersion:RestoreManagedPrefixListVersion' :: Integer
previousVersion = Integer
pPreviousVersion_,
        $sel:currentVersion:RestoreManagedPrefixListVersion' :: Integer
currentVersion = Integer
pCurrentVersion_
      }

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

-- | The ID of the prefix list.
restoreManagedPrefixListVersion_prefixListId :: Lens.Lens' RestoreManagedPrefixListVersion Prelude.Text
restoreManagedPrefixListVersion_prefixListId :: Lens' RestoreManagedPrefixListVersion Text
restoreManagedPrefixListVersion_prefixListId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreManagedPrefixListVersion' {Text
prefixListId :: Text
$sel:prefixListId:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Text
prefixListId} -> Text
prefixListId) (\s :: RestoreManagedPrefixListVersion
s@RestoreManagedPrefixListVersion' {} Text
a -> RestoreManagedPrefixListVersion
s {$sel:prefixListId:RestoreManagedPrefixListVersion' :: Text
prefixListId = Text
a} :: RestoreManagedPrefixListVersion)

-- | The version to restore.
restoreManagedPrefixListVersion_previousVersion :: Lens.Lens' RestoreManagedPrefixListVersion Prelude.Integer
restoreManagedPrefixListVersion_previousVersion :: Lens' RestoreManagedPrefixListVersion Integer
restoreManagedPrefixListVersion_previousVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreManagedPrefixListVersion' {Integer
previousVersion :: Integer
$sel:previousVersion:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Integer
previousVersion} -> Integer
previousVersion) (\s :: RestoreManagedPrefixListVersion
s@RestoreManagedPrefixListVersion' {} Integer
a -> RestoreManagedPrefixListVersion
s {$sel:previousVersion:RestoreManagedPrefixListVersion' :: Integer
previousVersion = Integer
a} :: RestoreManagedPrefixListVersion)

-- | The current version number for the prefix list.
restoreManagedPrefixListVersion_currentVersion :: Lens.Lens' RestoreManagedPrefixListVersion Prelude.Integer
restoreManagedPrefixListVersion_currentVersion :: Lens' RestoreManagedPrefixListVersion Integer
restoreManagedPrefixListVersion_currentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreManagedPrefixListVersion' {Integer
currentVersion :: Integer
$sel:currentVersion:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Integer
currentVersion} -> Integer
currentVersion) (\s :: RestoreManagedPrefixListVersion
s@RestoreManagedPrefixListVersion' {} Integer
a -> RestoreManagedPrefixListVersion
s {$sel:currentVersion:RestoreManagedPrefixListVersion' :: Integer
currentVersion = Integer
a} :: RestoreManagedPrefixListVersion)

instance
  Core.AWSRequest
    RestoreManagedPrefixListVersion
  where
  type
    AWSResponse RestoreManagedPrefixListVersion =
      RestoreManagedPrefixListVersionResponse
  request :: (Service -> Service)
-> RestoreManagedPrefixListVersion
-> Request RestoreManagedPrefixListVersion
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 RestoreManagedPrefixListVersion
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse RestoreManagedPrefixListVersion)))
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 ManagedPrefixList
-> Int -> RestoreManagedPrefixListVersionResponse
RestoreManagedPrefixListVersionResponse'
            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
"prefixList")
            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
    RestoreManagedPrefixListVersion
  where
  hashWithSalt :: Int -> RestoreManagedPrefixListVersion -> Int
hashWithSalt
    Int
_salt
    RestoreManagedPrefixListVersion' {Integer
Maybe Bool
Text
currentVersion :: Integer
previousVersion :: Integer
prefixListId :: Text
dryRun :: Maybe Bool
$sel:currentVersion:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Integer
$sel:previousVersion:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Integer
$sel:prefixListId:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Text
$sel:dryRun:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> 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
prefixListId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Integer
previousVersion
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Integer
currentVersion

instance
  Prelude.NFData
    RestoreManagedPrefixListVersion
  where
  rnf :: RestoreManagedPrefixListVersion -> ()
rnf RestoreManagedPrefixListVersion' {Integer
Maybe Bool
Text
currentVersion :: Integer
previousVersion :: Integer
prefixListId :: Text
dryRun :: Maybe Bool
$sel:currentVersion:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Integer
$sel:previousVersion:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Integer
$sel:prefixListId:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Text
$sel:dryRun:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> 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
prefixListId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Integer
previousVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Integer
currentVersion

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

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

instance Data.ToQuery RestoreManagedPrefixListVersion where
  toQuery :: RestoreManagedPrefixListVersion -> QueryString
toQuery RestoreManagedPrefixListVersion' {Integer
Maybe Bool
Text
currentVersion :: Integer
previousVersion :: Integer
prefixListId :: Text
dryRun :: Maybe Bool
$sel:currentVersion:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Integer
$sel:previousVersion:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Integer
$sel:prefixListId:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Text
$sel:dryRun:RestoreManagedPrefixListVersion' :: RestoreManagedPrefixListVersion -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"RestoreManagedPrefixListVersion" ::
                      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
"PrefixListId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
prefixListId,
        ByteString
"PreviousVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Integer
previousVersion,
        ByteString
"CurrentVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Integer
currentVersion
      ]

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

-- |
-- Create a value of 'RestoreManagedPrefixListVersionResponse' 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:
--
-- 'prefixList', 'restoreManagedPrefixListVersionResponse_prefixList' - Information about the prefix list.
--
-- 'httpStatus', 'restoreManagedPrefixListVersionResponse_httpStatus' - The response's http status code.
newRestoreManagedPrefixListVersionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RestoreManagedPrefixListVersionResponse
newRestoreManagedPrefixListVersionResponse :: Int -> RestoreManagedPrefixListVersionResponse
newRestoreManagedPrefixListVersionResponse
  Int
pHttpStatus_ =
    RestoreManagedPrefixListVersionResponse'
      { $sel:prefixList:RestoreManagedPrefixListVersionResponse' :: Maybe ManagedPrefixList
prefixList =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:RestoreManagedPrefixListVersionResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Information about the prefix list.
restoreManagedPrefixListVersionResponse_prefixList :: Lens.Lens' RestoreManagedPrefixListVersionResponse (Prelude.Maybe ManagedPrefixList)
restoreManagedPrefixListVersionResponse_prefixList :: Lens'
  RestoreManagedPrefixListVersionResponse (Maybe ManagedPrefixList)
restoreManagedPrefixListVersionResponse_prefixList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreManagedPrefixListVersionResponse' {Maybe ManagedPrefixList
prefixList :: Maybe ManagedPrefixList
$sel:prefixList:RestoreManagedPrefixListVersionResponse' :: RestoreManagedPrefixListVersionResponse -> Maybe ManagedPrefixList
prefixList} -> Maybe ManagedPrefixList
prefixList) (\s :: RestoreManagedPrefixListVersionResponse
s@RestoreManagedPrefixListVersionResponse' {} Maybe ManagedPrefixList
a -> RestoreManagedPrefixListVersionResponse
s {$sel:prefixList:RestoreManagedPrefixListVersionResponse' :: Maybe ManagedPrefixList
prefixList = Maybe ManagedPrefixList
a} :: RestoreManagedPrefixListVersionResponse)

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

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