{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.SnapshotInfo
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.EC2.Types.SnapshotInfo where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import Amazonka.EC2.Types.SnapshotState
import Amazonka.EC2.Types.Tag
import qualified Amazonka.Prelude as Prelude

-- | Information about a snapshot.
--
-- /See:/ 'newSnapshotInfo' smart constructor.
data SnapshotInfo = SnapshotInfo'
  { -- | Description specified by the CreateSnapshotRequest that has been applied
    -- to all snapshots.
    SnapshotInfo -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether the snapshot is encrypted.
    SnapshotInfo -> Maybe Bool
encrypted :: Prelude.Maybe Prelude.Bool,
    -- | The ARN of the Outpost on which the snapshot is stored. For more
    -- information, see
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/snapshots-outposts.html Amazon EBS local snapshots on Outposts>
    -- in the /Amazon Elastic Compute Cloud User Guide/.
    SnapshotInfo -> Maybe Text
outpostArn :: Prelude.Maybe Prelude.Text,
    -- | Account id used when creating this snapshot.
    SnapshotInfo -> Maybe Text
ownerId :: Prelude.Maybe Prelude.Text,
    -- | Progress this snapshot has made towards completing.
    SnapshotInfo -> Maybe Text
progress :: Prelude.Maybe Prelude.Text,
    -- | Snapshot id that can be used to describe this snapshot.
    SnapshotInfo -> Maybe Text
snapshotId :: Prelude.Maybe Prelude.Text,
    -- | Time this snapshot was started. This is the same for all snapshots
    -- initiated by the same request.
    SnapshotInfo -> Maybe ISO8601
startTime :: Prelude.Maybe Data.ISO8601,
    -- | Current state of the snapshot.
    SnapshotInfo -> Maybe SnapshotState
state :: Prelude.Maybe SnapshotState,
    -- | Tags associated with this snapshot.
    SnapshotInfo -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | Source volume from which this snapshot was created.
    SnapshotInfo -> Maybe Text
volumeId :: Prelude.Maybe Prelude.Text,
    -- | Size of the volume from which this snapshot was created.
    SnapshotInfo -> Maybe Int
volumeSize :: Prelude.Maybe Prelude.Int
  }
  deriving (SnapshotInfo -> SnapshotInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SnapshotInfo -> SnapshotInfo -> Bool
$c/= :: SnapshotInfo -> SnapshotInfo -> Bool
== :: SnapshotInfo -> SnapshotInfo -> Bool
$c== :: SnapshotInfo -> SnapshotInfo -> Bool
Prelude.Eq, ReadPrec [SnapshotInfo]
ReadPrec SnapshotInfo
Int -> ReadS SnapshotInfo
ReadS [SnapshotInfo]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SnapshotInfo]
$creadListPrec :: ReadPrec [SnapshotInfo]
readPrec :: ReadPrec SnapshotInfo
$creadPrec :: ReadPrec SnapshotInfo
readList :: ReadS [SnapshotInfo]
$creadList :: ReadS [SnapshotInfo]
readsPrec :: Int -> ReadS SnapshotInfo
$creadsPrec :: Int -> ReadS SnapshotInfo
Prelude.Read, Int -> SnapshotInfo -> ShowS
[SnapshotInfo] -> ShowS
SnapshotInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SnapshotInfo] -> ShowS
$cshowList :: [SnapshotInfo] -> ShowS
show :: SnapshotInfo -> String
$cshow :: SnapshotInfo -> String
showsPrec :: Int -> SnapshotInfo -> ShowS
$cshowsPrec :: Int -> SnapshotInfo -> ShowS
Prelude.Show, forall x. Rep SnapshotInfo x -> SnapshotInfo
forall x. SnapshotInfo -> Rep SnapshotInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SnapshotInfo x -> SnapshotInfo
$cfrom :: forall x. SnapshotInfo -> Rep SnapshotInfo x
Prelude.Generic)

-- |
-- Create a value of 'SnapshotInfo' 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:
--
-- 'description', 'snapshotInfo_description' - Description specified by the CreateSnapshotRequest that has been applied
-- to all snapshots.
--
-- 'encrypted', 'snapshotInfo_encrypted' - Indicates whether the snapshot is encrypted.
--
-- 'outpostArn', 'snapshotInfo_outpostArn' - The ARN of the Outpost on which the snapshot is stored. For more
-- information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/snapshots-outposts.html Amazon EBS local snapshots on Outposts>
-- in the /Amazon Elastic Compute Cloud User Guide/.
--
-- 'ownerId', 'snapshotInfo_ownerId' - Account id used when creating this snapshot.
--
-- 'progress', 'snapshotInfo_progress' - Progress this snapshot has made towards completing.
--
-- 'snapshotId', 'snapshotInfo_snapshotId' - Snapshot id that can be used to describe this snapshot.
--
-- 'startTime', 'snapshotInfo_startTime' - Time this snapshot was started. This is the same for all snapshots
-- initiated by the same request.
--
-- 'state', 'snapshotInfo_state' - Current state of the snapshot.
--
-- 'tags', 'snapshotInfo_tags' - Tags associated with this snapshot.
--
-- 'volumeId', 'snapshotInfo_volumeId' - Source volume from which this snapshot was created.
--
-- 'volumeSize', 'snapshotInfo_volumeSize' - Size of the volume from which this snapshot was created.
newSnapshotInfo ::
  SnapshotInfo
newSnapshotInfo :: SnapshotInfo
newSnapshotInfo =
  SnapshotInfo'
    { $sel:description:SnapshotInfo' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:encrypted:SnapshotInfo' :: Maybe Bool
encrypted = forall a. Maybe a
Prelude.Nothing,
      $sel:outpostArn:SnapshotInfo' :: Maybe Text
outpostArn = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerId:SnapshotInfo' :: Maybe Text
ownerId = forall a. Maybe a
Prelude.Nothing,
      $sel:progress:SnapshotInfo' :: Maybe Text
progress = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotId:SnapshotInfo' :: Maybe Text
snapshotId = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:SnapshotInfo' :: Maybe ISO8601
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:state:SnapshotInfo' :: Maybe SnapshotState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:SnapshotInfo' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeId:SnapshotInfo' :: Maybe Text
volumeId = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeSize:SnapshotInfo' :: Maybe Int
volumeSize = forall a. Maybe a
Prelude.Nothing
    }

-- | Description specified by the CreateSnapshotRequest that has been applied
-- to all snapshots.
snapshotInfo_description :: Lens.Lens' SnapshotInfo (Prelude.Maybe Prelude.Text)
snapshotInfo_description :: Lens' SnapshotInfo (Maybe Text)
snapshotInfo_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe Text
description :: Maybe Text
$sel:description:SnapshotInfo' :: SnapshotInfo -> Maybe Text
description} -> Maybe Text
description) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe Text
a -> SnapshotInfo
s {$sel:description:SnapshotInfo' :: Maybe Text
description = Maybe Text
a} :: SnapshotInfo)

-- | Indicates whether the snapshot is encrypted.
snapshotInfo_encrypted :: Lens.Lens' SnapshotInfo (Prelude.Maybe Prelude.Bool)
snapshotInfo_encrypted :: Lens' SnapshotInfo (Maybe Bool)
snapshotInfo_encrypted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe Bool
encrypted :: Maybe Bool
$sel:encrypted:SnapshotInfo' :: SnapshotInfo -> Maybe Bool
encrypted} -> Maybe Bool
encrypted) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe Bool
a -> SnapshotInfo
s {$sel:encrypted:SnapshotInfo' :: Maybe Bool
encrypted = Maybe Bool
a} :: SnapshotInfo)

-- | The ARN of the Outpost on which the snapshot is stored. For more
-- information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/snapshots-outposts.html Amazon EBS local snapshots on Outposts>
-- in the /Amazon Elastic Compute Cloud User Guide/.
snapshotInfo_outpostArn :: Lens.Lens' SnapshotInfo (Prelude.Maybe Prelude.Text)
snapshotInfo_outpostArn :: Lens' SnapshotInfo (Maybe Text)
snapshotInfo_outpostArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe Text
outpostArn :: Maybe Text
$sel:outpostArn:SnapshotInfo' :: SnapshotInfo -> Maybe Text
outpostArn} -> Maybe Text
outpostArn) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe Text
a -> SnapshotInfo
s {$sel:outpostArn:SnapshotInfo' :: Maybe Text
outpostArn = Maybe Text
a} :: SnapshotInfo)

-- | Account id used when creating this snapshot.
snapshotInfo_ownerId :: Lens.Lens' SnapshotInfo (Prelude.Maybe Prelude.Text)
snapshotInfo_ownerId :: Lens' SnapshotInfo (Maybe Text)
snapshotInfo_ownerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe Text
ownerId :: Maybe Text
$sel:ownerId:SnapshotInfo' :: SnapshotInfo -> Maybe Text
ownerId} -> Maybe Text
ownerId) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe Text
a -> SnapshotInfo
s {$sel:ownerId:SnapshotInfo' :: Maybe Text
ownerId = Maybe Text
a} :: SnapshotInfo)

-- | Progress this snapshot has made towards completing.
snapshotInfo_progress :: Lens.Lens' SnapshotInfo (Prelude.Maybe Prelude.Text)
snapshotInfo_progress :: Lens' SnapshotInfo (Maybe Text)
snapshotInfo_progress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe Text
progress :: Maybe Text
$sel:progress:SnapshotInfo' :: SnapshotInfo -> Maybe Text
progress} -> Maybe Text
progress) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe Text
a -> SnapshotInfo
s {$sel:progress:SnapshotInfo' :: Maybe Text
progress = Maybe Text
a} :: SnapshotInfo)

-- | Snapshot id that can be used to describe this snapshot.
snapshotInfo_snapshotId :: Lens.Lens' SnapshotInfo (Prelude.Maybe Prelude.Text)
snapshotInfo_snapshotId :: Lens' SnapshotInfo (Maybe Text)
snapshotInfo_snapshotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe Text
snapshotId :: Maybe Text
$sel:snapshotId:SnapshotInfo' :: SnapshotInfo -> Maybe Text
snapshotId} -> Maybe Text
snapshotId) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe Text
a -> SnapshotInfo
s {$sel:snapshotId:SnapshotInfo' :: Maybe Text
snapshotId = Maybe Text
a} :: SnapshotInfo)

-- | Time this snapshot was started. This is the same for all snapshots
-- initiated by the same request.
snapshotInfo_startTime :: Lens.Lens' SnapshotInfo (Prelude.Maybe Prelude.UTCTime)
snapshotInfo_startTime :: Lens' SnapshotInfo (Maybe UTCTime)
snapshotInfo_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe ISO8601
startTime :: Maybe ISO8601
$sel:startTime:SnapshotInfo' :: SnapshotInfo -> Maybe ISO8601
startTime} -> Maybe ISO8601
startTime) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe ISO8601
a -> SnapshotInfo
s {$sel:startTime:SnapshotInfo' :: Maybe ISO8601
startTime = Maybe ISO8601
a} :: SnapshotInfo) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Current state of the snapshot.
snapshotInfo_state :: Lens.Lens' SnapshotInfo (Prelude.Maybe SnapshotState)
snapshotInfo_state :: Lens' SnapshotInfo (Maybe SnapshotState)
snapshotInfo_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe SnapshotState
state :: Maybe SnapshotState
$sel:state:SnapshotInfo' :: SnapshotInfo -> Maybe SnapshotState
state} -> Maybe SnapshotState
state) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe SnapshotState
a -> SnapshotInfo
s {$sel:state:SnapshotInfo' :: Maybe SnapshotState
state = Maybe SnapshotState
a} :: SnapshotInfo)

-- | Tags associated with this snapshot.
snapshotInfo_tags :: Lens.Lens' SnapshotInfo (Prelude.Maybe [Tag])
snapshotInfo_tags :: Lens' SnapshotInfo (Maybe [Tag])
snapshotInfo_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:SnapshotInfo' :: SnapshotInfo -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe [Tag]
a -> SnapshotInfo
s {$sel:tags:SnapshotInfo' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: SnapshotInfo) 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

-- | Source volume from which this snapshot was created.
snapshotInfo_volumeId :: Lens.Lens' SnapshotInfo (Prelude.Maybe Prelude.Text)
snapshotInfo_volumeId :: Lens' SnapshotInfo (Maybe Text)
snapshotInfo_volumeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe Text
volumeId :: Maybe Text
$sel:volumeId:SnapshotInfo' :: SnapshotInfo -> Maybe Text
volumeId} -> Maybe Text
volumeId) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe Text
a -> SnapshotInfo
s {$sel:volumeId:SnapshotInfo' :: Maybe Text
volumeId = Maybe Text
a} :: SnapshotInfo)

-- | Size of the volume from which this snapshot was created.
snapshotInfo_volumeSize :: Lens.Lens' SnapshotInfo (Prelude.Maybe Prelude.Int)
snapshotInfo_volumeSize :: Lens' SnapshotInfo (Maybe Int)
snapshotInfo_volumeSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SnapshotInfo' {Maybe Int
volumeSize :: Maybe Int
$sel:volumeSize:SnapshotInfo' :: SnapshotInfo -> Maybe Int
volumeSize} -> Maybe Int
volumeSize) (\s :: SnapshotInfo
s@SnapshotInfo' {} Maybe Int
a -> SnapshotInfo
s {$sel:volumeSize:SnapshotInfo' :: Maybe Int
volumeSize = Maybe Int
a} :: SnapshotInfo)

instance Data.FromXML SnapshotInfo where
  parseXML :: [Node] -> Either String SnapshotInfo
parseXML [Node]
x =
    Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe SnapshotState
-> Maybe [Tag]
-> Maybe Text
-> Maybe Int
-> SnapshotInfo
SnapshotInfo'
      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
"description")
      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
"encrypted")
      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
"outpostArn")
      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
"ownerId")
      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
"progress")
      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.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"startTime")
      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
"state")
      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
"tagSet"
                      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
"volumeId")
      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
"volumeSize")

instance Prelude.Hashable SnapshotInfo where
  hashWithSalt :: Int -> SnapshotInfo -> Int
hashWithSalt Int
_salt SnapshotInfo' {Maybe Bool
Maybe Int
Maybe [Tag]
Maybe Text
Maybe ISO8601
Maybe SnapshotState
volumeSize :: Maybe Int
volumeId :: Maybe Text
tags :: Maybe [Tag]
state :: Maybe SnapshotState
startTime :: Maybe ISO8601
snapshotId :: Maybe Text
progress :: Maybe Text
ownerId :: Maybe Text
outpostArn :: Maybe Text
encrypted :: Maybe Bool
description :: Maybe Text
$sel:volumeSize:SnapshotInfo' :: SnapshotInfo -> Maybe Int
$sel:volumeId:SnapshotInfo' :: SnapshotInfo -> Maybe Text
$sel:tags:SnapshotInfo' :: SnapshotInfo -> Maybe [Tag]
$sel:state:SnapshotInfo' :: SnapshotInfo -> Maybe SnapshotState
$sel:startTime:SnapshotInfo' :: SnapshotInfo -> Maybe ISO8601
$sel:snapshotId:SnapshotInfo' :: SnapshotInfo -> Maybe Text
$sel:progress:SnapshotInfo' :: SnapshotInfo -> Maybe Text
$sel:ownerId:SnapshotInfo' :: SnapshotInfo -> Maybe Text
$sel:outpostArn:SnapshotInfo' :: SnapshotInfo -> Maybe Text
$sel:encrypted:SnapshotInfo' :: SnapshotInfo -> Maybe Bool
$sel:description:SnapshotInfo' :: SnapshotInfo -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
encrypted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
outpostArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ownerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
progress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snapshotId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SnapshotState
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
volumeId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
volumeSize

instance Prelude.NFData SnapshotInfo where
  rnf :: SnapshotInfo -> ()
rnf SnapshotInfo' {Maybe Bool
Maybe Int
Maybe [Tag]
Maybe Text
Maybe ISO8601
Maybe SnapshotState
volumeSize :: Maybe Int
volumeId :: Maybe Text
tags :: Maybe [Tag]
state :: Maybe SnapshotState
startTime :: Maybe ISO8601
snapshotId :: Maybe Text
progress :: Maybe Text
ownerId :: Maybe Text
outpostArn :: Maybe Text
encrypted :: Maybe Bool
description :: Maybe Text
$sel:volumeSize:SnapshotInfo' :: SnapshotInfo -> Maybe Int
$sel:volumeId:SnapshotInfo' :: SnapshotInfo -> Maybe Text
$sel:tags:SnapshotInfo' :: SnapshotInfo -> Maybe [Tag]
$sel:state:SnapshotInfo' :: SnapshotInfo -> Maybe SnapshotState
$sel:startTime:SnapshotInfo' :: SnapshotInfo -> Maybe ISO8601
$sel:snapshotId:SnapshotInfo' :: SnapshotInfo -> Maybe Text
$sel:progress:SnapshotInfo' :: SnapshotInfo -> Maybe Text
$sel:ownerId:SnapshotInfo' :: SnapshotInfo -> Maybe Text
$sel:outpostArn:SnapshotInfo' :: SnapshotInfo -> Maybe Text
$sel:encrypted:SnapshotInfo' :: SnapshotInfo -> Maybe Bool
$sel:description:SnapshotInfo' :: SnapshotInfo -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
encrypted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
outpostArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ownerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
progress
      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 Maybe ISO8601
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SnapshotState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
volumeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
volumeSize