{-# 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.ImageBuilder.Types.ImageSummary
-- 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.ImageBuilder.Types.ImageSummary where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ImageBuilder.Types.BuildType
import Amazonka.ImageBuilder.Types.ImageState
import Amazonka.ImageBuilder.Types.ImageType
import Amazonka.ImageBuilder.Types.OutputResources
import Amazonka.ImageBuilder.Types.Platform
import qualified Amazonka.Prelude as Prelude

-- | An image summary.
--
-- /See:/ 'newImageSummary' smart constructor.
data ImageSummary = ImageSummary'
  { -- | The Amazon Resource Name (ARN) of the image.
    ImageSummary -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | Indicates the type of build that created this image. The build can be
    -- initiated in the following ways:
    --
    -- -   __USER_INITIATED__ – A manual pipeline build request.
    --
    -- -   __SCHEDULED__ – A pipeline build initiated by a cron expression in
    --     the Image Builder pipeline, or from EventBridge.
    --
    -- -   __IMPORT__ – A VM import created the image to use as the base image
    --     for the recipe.
    ImageSummary -> Maybe BuildType
buildType :: Prelude.Maybe BuildType,
    -- | The date on which this image was created.
    ImageSummary -> Maybe Text
dateCreated :: Prelude.Maybe Prelude.Text,
    -- | The name of the image.
    ImageSummary -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The operating system version of the instance. For example, Amazon Linux
    -- 2, Ubuntu 18, or Microsoft Windows Server 2019.
    ImageSummary -> Maybe Text
osVersion :: Prelude.Maybe Prelude.Text,
    -- | The output resources produced when creating this image.
    ImageSummary -> Maybe OutputResources
outputResources :: Prelude.Maybe OutputResources,
    -- | The owner of the image.
    ImageSummary -> Maybe Text
owner :: Prelude.Maybe Prelude.Text,
    -- | The platform of the image.
    ImageSummary -> Maybe Platform
platform :: Prelude.Maybe Platform,
    -- | The state of the image.
    ImageSummary -> Maybe ImageState
state :: Prelude.Maybe ImageState,
    -- | The tags of the image.
    ImageSummary -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Specifies whether this is an AMI or container image.
    ImageSummary -> Maybe ImageType
type' :: Prelude.Maybe ImageType,
    -- | The version of the image.
    ImageSummary -> Maybe Text
version :: Prelude.Maybe Prelude.Text
  }
  deriving (ImageSummary -> ImageSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageSummary -> ImageSummary -> Bool
$c/= :: ImageSummary -> ImageSummary -> Bool
== :: ImageSummary -> ImageSummary -> Bool
$c== :: ImageSummary -> ImageSummary -> Bool
Prelude.Eq, ReadPrec [ImageSummary]
ReadPrec ImageSummary
Int -> ReadS ImageSummary
ReadS [ImageSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImageSummary]
$creadListPrec :: ReadPrec [ImageSummary]
readPrec :: ReadPrec ImageSummary
$creadPrec :: ReadPrec ImageSummary
readList :: ReadS [ImageSummary]
$creadList :: ReadS [ImageSummary]
readsPrec :: Int -> ReadS ImageSummary
$creadsPrec :: Int -> ReadS ImageSummary
Prelude.Read, Int -> ImageSummary -> ShowS
[ImageSummary] -> ShowS
ImageSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImageSummary] -> ShowS
$cshowList :: [ImageSummary] -> ShowS
show :: ImageSummary -> String
$cshow :: ImageSummary -> String
showsPrec :: Int -> ImageSummary -> ShowS
$cshowsPrec :: Int -> ImageSummary -> ShowS
Prelude.Show, forall x. Rep ImageSummary x -> ImageSummary
forall x. ImageSummary -> Rep ImageSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImageSummary x -> ImageSummary
$cfrom :: forall x. ImageSummary -> Rep ImageSummary x
Prelude.Generic)

-- |
-- Create a value of 'ImageSummary' 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:
--
-- 'arn', 'imageSummary_arn' - The Amazon Resource Name (ARN) of the image.
--
-- 'buildType', 'imageSummary_buildType' - Indicates the type of build that created this image. The build can be
-- initiated in the following ways:
--
-- -   __USER_INITIATED__ – A manual pipeline build request.
--
-- -   __SCHEDULED__ – A pipeline build initiated by a cron expression in
--     the Image Builder pipeline, or from EventBridge.
--
-- -   __IMPORT__ – A VM import created the image to use as the base image
--     for the recipe.
--
-- 'dateCreated', 'imageSummary_dateCreated' - The date on which this image was created.
--
-- 'name', 'imageSummary_name' - The name of the image.
--
-- 'osVersion', 'imageSummary_osVersion' - The operating system version of the instance. For example, Amazon Linux
-- 2, Ubuntu 18, or Microsoft Windows Server 2019.
--
-- 'outputResources', 'imageSummary_outputResources' - The output resources produced when creating this image.
--
-- 'owner', 'imageSummary_owner' - The owner of the image.
--
-- 'platform', 'imageSummary_platform' - The platform of the image.
--
-- 'state', 'imageSummary_state' - The state of the image.
--
-- 'tags', 'imageSummary_tags' - The tags of the image.
--
-- 'type'', 'imageSummary_type' - Specifies whether this is an AMI or container image.
--
-- 'version', 'imageSummary_version' - The version of the image.
newImageSummary ::
  ImageSummary
newImageSummary :: ImageSummary
newImageSummary =
  ImageSummary'
    { $sel:arn:ImageSummary' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:buildType:ImageSummary' :: Maybe BuildType
buildType = forall a. Maybe a
Prelude.Nothing,
      $sel:dateCreated:ImageSummary' :: Maybe Text
dateCreated = forall a. Maybe a
Prelude.Nothing,
      $sel:name:ImageSummary' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:osVersion:ImageSummary' :: Maybe Text
osVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:outputResources:ImageSummary' :: Maybe OutputResources
outputResources = forall a. Maybe a
Prelude.Nothing,
      $sel:owner:ImageSummary' :: Maybe Text
owner = forall a. Maybe a
Prelude.Nothing,
      $sel:platform:ImageSummary' :: Maybe Platform
platform = forall a. Maybe a
Prelude.Nothing,
      $sel:state:ImageSummary' :: Maybe ImageState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ImageSummary' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:type':ImageSummary' :: Maybe ImageType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:version:ImageSummary' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the image.
imageSummary_arn :: Lens.Lens' ImageSummary (Prelude.Maybe Prelude.Text)
imageSummary_arn :: Lens' ImageSummary (Maybe Text)
imageSummary_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe Text
arn :: Maybe Text
$sel:arn:ImageSummary' :: ImageSummary -> Maybe Text
arn} -> Maybe Text
arn) (\s :: ImageSummary
s@ImageSummary' {} Maybe Text
a -> ImageSummary
s {$sel:arn:ImageSummary' :: Maybe Text
arn = Maybe Text
a} :: ImageSummary)

-- | Indicates the type of build that created this image. The build can be
-- initiated in the following ways:
--
-- -   __USER_INITIATED__ – A manual pipeline build request.
--
-- -   __SCHEDULED__ – A pipeline build initiated by a cron expression in
--     the Image Builder pipeline, or from EventBridge.
--
-- -   __IMPORT__ – A VM import created the image to use as the base image
--     for the recipe.
imageSummary_buildType :: Lens.Lens' ImageSummary (Prelude.Maybe BuildType)
imageSummary_buildType :: Lens' ImageSummary (Maybe BuildType)
imageSummary_buildType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe BuildType
buildType :: Maybe BuildType
$sel:buildType:ImageSummary' :: ImageSummary -> Maybe BuildType
buildType} -> Maybe BuildType
buildType) (\s :: ImageSummary
s@ImageSummary' {} Maybe BuildType
a -> ImageSummary
s {$sel:buildType:ImageSummary' :: Maybe BuildType
buildType = Maybe BuildType
a} :: ImageSummary)

-- | The date on which this image was created.
imageSummary_dateCreated :: Lens.Lens' ImageSummary (Prelude.Maybe Prelude.Text)
imageSummary_dateCreated :: Lens' ImageSummary (Maybe Text)
imageSummary_dateCreated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe Text
dateCreated :: Maybe Text
$sel:dateCreated:ImageSummary' :: ImageSummary -> Maybe Text
dateCreated} -> Maybe Text
dateCreated) (\s :: ImageSummary
s@ImageSummary' {} Maybe Text
a -> ImageSummary
s {$sel:dateCreated:ImageSummary' :: Maybe Text
dateCreated = Maybe Text
a} :: ImageSummary)

-- | The name of the image.
imageSummary_name :: Lens.Lens' ImageSummary (Prelude.Maybe Prelude.Text)
imageSummary_name :: Lens' ImageSummary (Maybe Text)
imageSummary_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe Text
name :: Maybe Text
$sel:name:ImageSummary' :: ImageSummary -> Maybe Text
name} -> Maybe Text
name) (\s :: ImageSummary
s@ImageSummary' {} Maybe Text
a -> ImageSummary
s {$sel:name:ImageSummary' :: Maybe Text
name = Maybe Text
a} :: ImageSummary)

-- | The operating system version of the instance. For example, Amazon Linux
-- 2, Ubuntu 18, or Microsoft Windows Server 2019.
imageSummary_osVersion :: Lens.Lens' ImageSummary (Prelude.Maybe Prelude.Text)
imageSummary_osVersion :: Lens' ImageSummary (Maybe Text)
imageSummary_osVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe Text
osVersion :: Maybe Text
$sel:osVersion:ImageSummary' :: ImageSummary -> Maybe Text
osVersion} -> Maybe Text
osVersion) (\s :: ImageSummary
s@ImageSummary' {} Maybe Text
a -> ImageSummary
s {$sel:osVersion:ImageSummary' :: Maybe Text
osVersion = Maybe Text
a} :: ImageSummary)

-- | The output resources produced when creating this image.
imageSummary_outputResources :: Lens.Lens' ImageSummary (Prelude.Maybe OutputResources)
imageSummary_outputResources :: Lens' ImageSummary (Maybe OutputResources)
imageSummary_outputResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe OutputResources
outputResources :: Maybe OutputResources
$sel:outputResources:ImageSummary' :: ImageSummary -> Maybe OutputResources
outputResources} -> Maybe OutputResources
outputResources) (\s :: ImageSummary
s@ImageSummary' {} Maybe OutputResources
a -> ImageSummary
s {$sel:outputResources:ImageSummary' :: Maybe OutputResources
outputResources = Maybe OutputResources
a} :: ImageSummary)

-- | The owner of the image.
imageSummary_owner :: Lens.Lens' ImageSummary (Prelude.Maybe Prelude.Text)
imageSummary_owner :: Lens' ImageSummary (Maybe Text)
imageSummary_owner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe Text
owner :: Maybe Text
$sel:owner:ImageSummary' :: ImageSummary -> Maybe Text
owner} -> Maybe Text
owner) (\s :: ImageSummary
s@ImageSummary' {} Maybe Text
a -> ImageSummary
s {$sel:owner:ImageSummary' :: Maybe Text
owner = Maybe Text
a} :: ImageSummary)

-- | The platform of the image.
imageSummary_platform :: Lens.Lens' ImageSummary (Prelude.Maybe Platform)
imageSummary_platform :: Lens' ImageSummary (Maybe Platform)
imageSummary_platform = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe Platform
platform :: Maybe Platform
$sel:platform:ImageSummary' :: ImageSummary -> Maybe Platform
platform} -> Maybe Platform
platform) (\s :: ImageSummary
s@ImageSummary' {} Maybe Platform
a -> ImageSummary
s {$sel:platform:ImageSummary' :: Maybe Platform
platform = Maybe Platform
a} :: ImageSummary)

-- | The state of the image.
imageSummary_state :: Lens.Lens' ImageSummary (Prelude.Maybe ImageState)
imageSummary_state :: Lens' ImageSummary (Maybe ImageState)
imageSummary_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe ImageState
state :: Maybe ImageState
$sel:state:ImageSummary' :: ImageSummary -> Maybe ImageState
state} -> Maybe ImageState
state) (\s :: ImageSummary
s@ImageSummary' {} Maybe ImageState
a -> ImageSummary
s {$sel:state:ImageSummary' :: Maybe ImageState
state = Maybe ImageState
a} :: ImageSummary)

-- | The tags of the image.
imageSummary_tags :: Lens.Lens' ImageSummary (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
imageSummary_tags :: Lens' ImageSummary (Maybe (HashMap Text Text))
imageSummary_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:ImageSummary' :: ImageSummary -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: ImageSummary
s@ImageSummary' {} Maybe (HashMap Text Text)
a -> ImageSummary
s {$sel:tags:ImageSummary' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: ImageSummary) 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

-- | Specifies whether this is an AMI or container image.
imageSummary_type :: Lens.Lens' ImageSummary (Prelude.Maybe ImageType)
imageSummary_type :: Lens' ImageSummary (Maybe ImageType)
imageSummary_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe ImageType
type' :: Maybe ImageType
$sel:type':ImageSummary' :: ImageSummary -> Maybe ImageType
type'} -> Maybe ImageType
type') (\s :: ImageSummary
s@ImageSummary' {} Maybe ImageType
a -> ImageSummary
s {$sel:type':ImageSummary' :: Maybe ImageType
type' = Maybe ImageType
a} :: ImageSummary)

-- | The version of the image.
imageSummary_version :: Lens.Lens' ImageSummary (Prelude.Maybe Prelude.Text)
imageSummary_version :: Lens' ImageSummary (Maybe Text)
imageSummary_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageSummary' {Maybe Text
version :: Maybe Text
$sel:version:ImageSummary' :: ImageSummary -> Maybe Text
version} -> Maybe Text
version) (\s :: ImageSummary
s@ImageSummary' {} Maybe Text
a -> ImageSummary
s {$sel:version:ImageSummary' :: Maybe Text
version = Maybe Text
a} :: ImageSummary)

instance Data.FromJSON ImageSummary where
  parseJSON :: Value -> Parser ImageSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ImageSummary"
      ( \Object
x ->
          Maybe Text
-> Maybe BuildType
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe OutputResources
-> Maybe Text
-> Maybe Platform
-> Maybe ImageState
-> Maybe (HashMap Text Text)
-> Maybe ImageType
-> Maybe Text
-> ImageSummary
ImageSummary'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"buildType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"dateCreated")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"osVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"outputResources")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"owner")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"platform")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"state")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"version")
      )

instance Prelude.Hashable ImageSummary where
  hashWithSalt :: Int -> ImageSummary -> Int
hashWithSalt Int
_salt ImageSummary' {Maybe Text
Maybe (HashMap Text Text)
Maybe BuildType
Maybe ImageState
Maybe ImageType
Maybe OutputResources
Maybe Platform
version :: Maybe Text
type' :: Maybe ImageType
tags :: Maybe (HashMap Text Text)
state :: Maybe ImageState
platform :: Maybe Platform
owner :: Maybe Text
outputResources :: Maybe OutputResources
osVersion :: Maybe Text
name :: Maybe Text
dateCreated :: Maybe Text
buildType :: Maybe BuildType
arn :: Maybe Text
$sel:version:ImageSummary' :: ImageSummary -> Maybe Text
$sel:type':ImageSummary' :: ImageSummary -> Maybe ImageType
$sel:tags:ImageSummary' :: ImageSummary -> Maybe (HashMap Text Text)
$sel:state:ImageSummary' :: ImageSummary -> Maybe ImageState
$sel:platform:ImageSummary' :: ImageSummary -> Maybe Platform
$sel:owner:ImageSummary' :: ImageSummary -> Maybe Text
$sel:outputResources:ImageSummary' :: ImageSummary -> Maybe OutputResources
$sel:osVersion:ImageSummary' :: ImageSummary -> Maybe Text
$sel:name:ImageSummary' :: ImageSummary -> Maybe Text
$sel:dateCreated:ImageSummary' :: ImageSummary -> Maybe Text
$sel:buildType:ImageSummary' :: ImageSummary -> Maybe BuildType
$sel:arn:ImageSummary' :: ImageSummary -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BuildType
buildType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dateCreated
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
osVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OutputResources
outputResources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
owner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Platform
platform
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ImageState
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ImageType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
version

instance Prelude.NFData ImageSummary where
  rnf :: ImageSummary -> ()
rnf ImageSummary' {Maybe Text
Maybe (HashMap Text Text)
Maybe BuildType
Maybe ImageState
Maybe ImageType
Maybe OutputResources
Maybe Platform
version :: Maybe Text
type' :: Maybe ImageType
tags :: Maybe (HashMap Text Text)
state :: Maybe ImageState
platform :: Maybe Platform
owner :: Maybe Text
outputResources :: Maybe OutputResources
osVersion :: Maybe Text
name :: Maybe Text
dateCreated :: Maybe Text
buildType :: Maybe BuildType
arn :: Maybe Text
$sel:version:ImageSummary' :: ImageSummary -> Maybe Text
$sel:type':ImageSummary' :: ImageSummary -> Maybe ImageType
$sel:tags:ImageSummary' :: ImageSummary -> Maybe (HashMap Text Text)
$sel:state:ImageSummary' :: ImageSummary -> Maybe ImageState
$sel:platform:ImageSummary' :: ImageSummary -> Maybe Platform
$sel:owner:ImageSummary' :: ImageSummary -> Maybe Text
$sel:outputResources:ImageSummary' :: ImageSummary -> Maybe OutputResources
$sel:osVersion:ImageSummary' :: ImageSummary -> Maybe Text
$sel:name:ImageSummary' :: ImageSummary -> Maybe Text
$sel:dateCreated:ImageSummary' :: ImageSummary -> Maybe Text
$sel:buildType:ImageSummary' :: ImageSummary -> Maybe BuildType
$sel:arn:ImageSummary' :: ImageSummary -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BuildType
buildType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dateCreated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
osVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OutputResources
outputResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
owner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Platform
platform
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImageState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImageType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
version