{-# 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.DescribeSnapshotAttribute
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the specified attribute of the specified snapshot. You can
-- specify only one attribute at a time.
--
-- For more information about EBS snapshots, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/EBSSnapshots.html Amazon EBS snapshots>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.DescribeSnapshotAttribute
  ( -- * Creating a Request
    DescribeSnapshotAttribute (..),
    newDescribeSnapshotAttribute,

    -- * Request Lenses
    describeSnapshotAttribute_dryRun,
    describeSnapshotAttribute_attribute,
    describeSnapshotAttribute_snapshotId,

    -- * Destructuring the Response
    DescribeSnapshotAttributeResponse (..),
    newDescribeSnapshotAttributeResponse,

    -- * Response Lenses
    describeSnapshotAttributeResponse_createVolumePermissions,
    describeSnapshotAttributeResponse_productCodes,
    describeSnapshotAttributeResponse_snapshotId,
    describeSnapshotAttributeResponse_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:/ 'newDescribeSnapshotAttribute' smart constructor.
data DescribeSnapshotAttribute = DescribeSnapshotAttribute'
  { -- | 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@.
    DescribeSnapshotAttribute -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The snapshot attribute you would like to view.
    DescribeSnapshotAttribute -> SnapshotAttributeName
attribute :: SnapshotAttributeName,
    -- | The ID of the EBS snapshot.
    DescribeSnapshotAttribute -> Text
snapshotId :: Prelude.Text
  }
  deriving (DescribeSnapshotAttribute -> DescribeSnapshotAttribute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSnapshotAttribute -> DescribeSnapshotAttribute -> Bool
$c/= :: DescribeSnapshotAttribute -> DescribeSnapshotAttribute -> Bool
== :: DescribeSnapshotAttribute -> DescribeSnapshotAttribute -> Bool
$c== :: DescribeSnapshotAttribute -> DescribeSnapshotAttribute -> Bool
Prelude.Eq, ReadPrec [DescribeSnapshotAttribute]
ReadPrec DescribeSnapshotAttribute
Int -> ReadS DescribeSnapshotAttribute
ReadS [DescribeSnapshotAttribute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSnapshotAttribute]
$creadListPrec :: ReadPrec [DescribeSnapshotAttribute]
readPrec :: ReadPrec DescribeSnapshotAttribute
$creadPrec :: ReadPrec DescribeSnapshotAttribute
readList :: ReadS [DescribeSnapshotAttribute]
$creadList :: ReadS [DescribeSnapshotAttribute]
readsPrec :: Int -> ReadS DescribeSnapshotAttribute
$creadsPrec :: Int -> ReadS DescribeSnapshotAttribute
Prelude.Read, Int -> DescribeSnapshotAttribute -> ShowS
[DescribeSnapshotAttribute] -> ShowS
DescribeSnapshotAttribute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSnapshotAttribute] -> ShowS
$cshowList :: [DescribeSnapshotAttribute] -> ShowS
show :: DescribeSnapshotAttribute -> String
$cshow :: DescribeSnapshotAttribute -> String
showsPrec :: Int -> DescribeSnapshotAttribute -> ShowS
$cshowsPrec :: Int -> DescribeSnapshotAttribute -> ShowS
Prelude.Show, forall x.
Rep DescribeSnapshotAttribute x -> DescribeSnapshotAttribute
forall x.
DescribeSnapshotAttribute -> Rep DescribeSnapshotAttribute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSnapshotAttribute x -> DescribeSnapshotAttribute
$cfrom :: forall x.
DescribeSnapshotAttribute -> Rep DescribeSnapshotAttribute x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSnapshotAttribute' 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', 'describeSnapshotAttribute_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@.
--
-- 'attribute', 'describeSnapshotAttribute_attribute' - The snapshot attribute you would like to view.
--
-- 'snapshotId', 'describeSnapshotAttribute_snapshotId' - The ID of the EBS snapshot.
newDescribeSnapshotAttribute ::
  -- | 'attribute'
  SnapshotAttributeName ->
  -- | 'snapshotId'
  Prelude.Text ->
  DescribeSnapshotAttribute
newDescribeSnapshotAttribute :: SnapshotAttributeName -> Text -> DescribeSnapshotAttribute
newDescribeSnapshotAttribute SnapshotAttributeName
pAttribute_ Text
pSnapshotId_ =
  DescribeSnapshotAttribute'
    { $sel:dryRun:DescribeSnapshotAttribute' :: Maybe Bool
dryRun =
        forall a. Maybe a
Prelude.Nothing,
      $sel:attribute:DescribeSnapshotAttribute' :: SnapshotAttributeName
attribute = SnapshotAttributeName
pAttribute_,
      $sel:snapshotId:DescribeSnapshotAttribute' :: Text
snapshotId = Text
pSnapshotId_
    }

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

-- | The snapshot attribute you would like to view.
describeSnapshotAttribute_attribute :: Lens.Lens' DescribeSnapshotAttribute SnapshotAttributeName
describeSnapshotAttribute_attribute :: Lens' DescribeSnapshotAttribute SnapshotAttributeName
describeSnapshotAttribute_attribute = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotAttribute' {SnapshotAttributeName
attribute :: SnapshotAttributeName
$sel:attribute:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> SnapshotAttributeName
attribute} -> SnapshotAttributeName
attribute) (\s :: DescribeSnapshotAttribute
s@DescribeSnapshotAttribute' {} SnapshotAttributeName
a -> DescribeSnapshotAttribute
s {$sel:attribute:DescribeSnapshotAttribute' :: SnapshotAttributeName
attribute = SnapshotAttributeName
a} :: DescribeSnapshotAttribute)

-- | The ID of the EBS snapshot.
describeSnapshotAttribute_snapshotId :: Lens.Lens' DescribeSnapshotAttribute Prelude.Text
describeSnapshotAttribute_snapshotId :: Lens' DescribeSnapshotAttribute Text
describeSnapshotAttribute_snapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotAttribute' {Text
snapshotId :: Text
$sel:snapshotId:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> Text
snapshotId} -> Text
snapshotId) (\s :: DescribeSnapshotAttribute
s@DescribeSnapshotAttribute' {} Text
a -> DescribeSnapshotAttribute
s {$sel:snapshotId:DescribeSnapshotAttribute' :: Text
snapshotId = Text
a} :: DescribeSnapshotAttribute)

instance Core.AWSRequest DescribeSnapshotAttribute where
  type
    AWSResponse DescribeSnapshotAttribute =
      DescribeSnapshotAttributeResponse
  request :: (Service -> Service)
-> DescribeSnapshotAttribute -> Request DescribeSnapshotAttribute
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 DescribeSnapshotAttribute
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeSnapshotAttribute)))
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 [CreateVolumePermission]
-> Maybe [ProductCode]
-> Maybe Text
-> Int
-> DescribeSnapshotAttributeResponse
DescribeSnapshotAttributeResponse'
            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
"createVolumePermission"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                        )
            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
"productCodes"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                        )
            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
"snapshotId")
            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 DescribeSnapshotAttribute where
  hashWithSalt :: Int -> DescribeSnapshotAttribute -> Int
hashWithSalt Int
_salt DescribeSnapshotAttribute' {Maybe Bool
Text
SnapshotAttributeName
snapshotId :: Text
attribute :: SnapshotAttributeName
dryRun :: Maybe Bool
$sel:snapshotId:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> Text
$sel:attribute:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> SnapshotAttributeName
$sel:dryRun:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> 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` SnapshotAttributeName
attribute
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
snapshotId

instance Prelude.NFData DescribeSnapshotAttribute where
  rnf :: DescribeSnapshotAttribute -> ()
rnf DescribeSnapshotAttribute' {Maybe Bool
Text
SnapshotAttributeName
snapshotId :: Text
attribute :: SnapshotAttributeName
dryRun :: Maybe Bool
$sel:snapshotId:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> Text
$sel:attribute:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> SnapshotAttributeName
$sel:dryRun:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> 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 SnapshotAttributeName
attribute
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
snapshotId

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

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

instance Data.ToQuery DescribeSnapshotAttribute where
  toQuery :: DescribeSnapshotAttribute -> QueryString
toQuery DescribeSnapshotAttribute' {Maybe Bool
Text
SnapshotAttributeName
snapshotId :: Text
attribute :: SnapshotAttributeName
dryRun :: Maybe Bool
$sel:snapshotId:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> Text
$sel:attribute:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> SnapshotAttributeName
$sel:dryRun:DescribeSnapshotAttribute' :: DescribeSnapshotAttribute -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeSnapshotAttribute" :: 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
"Attribute" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: SnapshotAttributeName
attribute,
        ByteString
"SnapshotId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
snapshotId
      ]

-- | /See:/ 'newDescribeSnapshotAttributeResponse' smart constructor.
data DescribeSnapshotAttributeResponse = DescribeSnapshotAttributeResponse'
  { -- | The users and groups that have the permissions for creating volumes from
    -- the snapshot.
    DescribeSnapshotAttributeResponse -> Maybe [CreateVolumePermission]
createVolumePermissions :: Prelude.Maybe [CreateVolumePermission],
    -- | The product codes.
    DescribeSnapshotAttributeResponse -> Maybe [ProductCode]
productCodes :: Prelude.Maybe [ProductCode],
    -- | The ID of the EBS snapshot.
    DescribeSnapshotAttributeResponse -> Maybe Text
snapshotId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeSnapshotAttributeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeSnapshotAttributeResponse
-> DescribeSnapshotAttributeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSnapshotAttributeResponse
-> DescribeSnapshotAttributeResponse -> Bool
$c/= :: DescribeSnapshotAttributeResponse
-> DescribeSnapshotAttributeResponse -> Bool
== :: DescribeSnapshotAttributeResponse
-> DescribeSnapshotAttributeResponse -> Bool
$c== :: DescribeSnapshotAttributeResponse
-> DescribeSnapshotAttributeResponse -> Bool
Prelude.Eq, ReadPrec [DescribeSnapshotAttributeResponse]
ReadPrec DescribeSnapshotAttributeResponse
Int -> ReadS DescribeSnapshotAttributeResponse
ReadS [DescribeSnapshotAttributeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSnapshotAttributeResponse]
$creadListPrec :: ReadPrec [DescribeSnapshotAttributeResponse]
readPrec :: ReadPrec DescribeSnapshotAttributeResponse
$creadPrec :: ReadPrec DescribeSnapshotAttributeResponse
readList :: ReadS [DescribeSnapshotAttributeResponse]
$creadList :: ReadS [DescribeSnapshotAttributeResponse]
readsPrec :: Int -> ReadS DescribeSnapshotAttributeResponse
$creadsPrec :: Int -> ReadS DescribeSnapshotAttributeResponse
Prelude.Read, Int -> DescribeSnapshotAttributeResponse -> ShowS
[DescribeSnapshotAttributeResponse] -> ShowS
DescribeSnapshotAttributeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSnapshotAttributeResponse] -> ShowS
$cshowList :: [DescribeSnapshotAttributeResponse] -> ShowS
show :: DescribeSnapshotAttributeResponse -> String
$cshow :: DescribeSnapshotAttributeResponse -> String
showsPrec :: Int -> DescribeSnapshotAttributeResponse -> ShowS
$cshowsPrec :: Int -> DescribeSnapshotAttributeResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeSnapshotAttributeResponse x
-> DescribeSnapshotAttributeResponse
forall x.
DescribeSnapshotAttributeResponse
-> Rep DescribeSnapshotAttributeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSnapshotAttributeResponse x
-> DescribeSnapshotAttributeResponse
$cfrom :: forall x.
DescribeSnapshotAttributeResponse
-> Rep DescribeSnapshotAttributeResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSnapshotAttributeResponse' 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:
--
-- 'createVolumePermissions', 'describeSnapshotAttributeResponse_createVolumePermissions' - The users and groups that have the permissions for creating volumes from
-- the snapshot.
--
-- 'productCodes', 'describeSnapshotAttributeResponse_productCodes' - The product codes.
--
-- 'snapshotId', 'describeSnapshotAttributeResponse_snapshotId' - The ID of the EBS snapshot.
--
-- 'httpStatus', 'describeSnapshotAttributeResponse_httpStatus' - The response's http status code.
newDescribeSnapshotAttributeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSnapshotAttributeResponse
newDescribeSnapshotAttributeResponse :: Int -> DescribeSnapshotAttributeResponse
newDescribeSnapshotAttributeResponse Int
pHttpStatus_ =
  DescribeSnapshotAttributeResponse'
    { $sel:createVolumePermissions:DescribeSnapshotAttributeResponse' :: Maybe [CreateVolumePermission]
createVolumePermissions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:productCodes:DescribeSnapshotAttributeResponse' :: Maybe [ProductCode]
productCodes = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotId:DescribeSnapshotAttributeResponse' :: Maybe Text
snapshotId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeSnapshotAttributeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The users and groups that have the permissions for creating volumes from
-- the snapshot.
describeSnapshotAttributeResponse_createVolumePermissions :: Lens.Lens' DescribeSnapshotAttributeResponse (Prelude.Maybe [CreateVolumePermission])
describeSnapshotAttributeResponse_createVolumePermissions :: Lens'
  DescribeSnapshotAttributeResponse (Maybe [CreateVolumePermission])
describeSnapshotAttributeResponse_createVolumePermissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotAttributeResponse' {Maybe [CreateVolumePermission]
createVolumePermissions :: Maybe [CreateVolumePermission]
$sel:createVolumePermissions:DescribeSnapshotAttributeResponse' :: DescribeSnapshotAttributeResponse -> Maybe [CreateVolumePermission]
createVolumePermissions} -> Maybe [CreateVolumePermission]
createVolumePermissions) (\s :: DescribeSnapshotAttributeResponse
s@DescribeSnapshotAttributeResponse' {} Maybe [CreateVolumePermission]
a -> DescribeSnapshotAttributeResponse
s {$sel:createVolumePermissions:DescribeSnapshotAttributeResponse' :: Maybe [CreateVolumePermission]
createVolumePermissions = Maybe [CreateVolumePermission]
a} :: DescribeSnapshotAttributeResponse) 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 product codes.
describeSnapshotAttributeResponse_productCodes :: Lens.Lens' DescribeSnapshotAttributeResponse (Prelude.Maybe [ProductCode])
describeSnapshotAttributeResponse_productCodes :: Lens' DescribeSnapshotAttributeResponse (Maybe [ProductCode])
describeSnapshotAttributeResponse_productCodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotAttributeResponse' {Maybe [ProductCode]
productCodes :: Maybe [ProductCode]
$sel:productCodes:DescribeSnapshotAttributeResponse' :: DescribeSnapshotAttributeResponse -> Maybe [ProductCode]
productCodes} -> Maybe [ProductCode]
productCodes) (\s :: DescribeSnapshotAttributeResponse
s@DescribeSnapshotAttributeResponse' {} Maybe [ProductCode]
a -> DescribeSnapshotAttributeResponse
s {$sel:productCodes:DescribeSnapshotAttributeResponse' :: Maybe [ProductCode]
productCodes = Maybe [ProductCode]
a} :: DescribeSnapshotAttributeResponse) 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 ID of the EBS snapshot.
describeSnapshotAttributeResponse_snapshotId :: Lens.Lens' DescribeSnapshotAttributeResponse (Prelude.Maybe Prelude.Text)
describeSnapshotAttributeResponse_snapshotId :: Lens' DescribeSnapshotAttributeResponse (Maybe Text)
describeSnapshotAttributeResponse_snapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotAttributeResponse' {Maybe Text
snapshotId :: Maybe Text
$sel:snapshotId:DescribeSnapshotAttributeResponse' :: DescribeSnapshotAttributeResponse -> Maybe Text
snapshotId} -> Maybe Text
snapshotId) (\s :: DescribeSnapshotAttributeResponse
s@DescribeSnapshotAttributeResponse' {} Maybe Text
a -> DescribeSnapshotAttributeResponse
s {$sel:snapshotId:DescribeSnapshotAttributeResponse' :: Maybe Text
snapshotId = Maybe Text
a} :: DescribeSnapshotAttributeResponse)

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

instance
  Prelude.NFData
    DescribeSnapshotAttributeResponse
  where
  rnf :: DescribeSnapshotAttributeResponse -> ()
rnf DescribeSnapshotAttributeResponse' {Int
Maybe [CreateVolumePermission]
Maybe [ProductCode]
Maybe Text
httpStatus :: Int
snapshotId :: Maybe Text
productCodes :: Maybe [ProductCode]
createVolumePermissions :: Maybe [CreateVolumePermission]
$sel:httpStatus:DescribeSnapshotAttributeResponse' :: DescribeSnapshotAttributeResponse -> Int
$sel:snapshotId:DescribeSnapshotAttributeResponse' :: DescribeSnapshotAttributeResponse -> Maybe Text
$sel:productCodes:DescribeSnapshotAttributeResponse' :: DescribeSnapshotAttributeResponse -> Maybe [ProductCode]
$sel:createVolumePermissions:DescribeSnapshotAttributeResponse' :: DescribeSnapshotAttributeResponse -> Maybe [CreateVolumePermission]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [CreateVolumePermission]
createVolumePermissions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ProductCode]
productCodes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
snapshotId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus