{-# 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.Image
-- 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.Image 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.ContainerRecipe
import Amazonka.ImageBuilder.Types.DistributionConfiguration
import Amazonka.ImageBuilder.Types.ImageRecipe
import Amazonka.ImageBuilder.Types.ImageState
import Amazonka.ImageBuilder.Types.ImageTestsConfiguration
import Amazonka.ImageBuilder.Types.ImageType
import Amazonka.ImageBuilder.Types.InfrastructureConfiguration
import Amazonka.ImageBuilder.Types.OutputResources
import Amazonka.ImageBuilder.Types.Platform
import qualified Amazonka.Prelude as Prelude

-- | An Image Builder image. You must specify exactly one recipe for the
-- image – either a container recipe (@containerRecipe@), which creates a
-- container image, or an image recipe (@imageRecipe@), which creates an
-- AMI.
--
-- /See:/ 'newImage' smart constructor.
data Image = Image'
  { -- | The Amazon Resource Name (ARN) of the image.
    --
    -- Semantic versioning is included in each object\'s Amazon Resource Name
    -- (ARN), at the level that applies to that object as follows:
    --
    -- 1.  Versionless ARNs and Name ARNs do not include specific values in any
    --     of the nodes. The nodes are either left off entirely, or they are
    --     specified as wildcards, for example: x.x.x.
    --
    -- 2.  Version ARNs have only the first three nodes:
    --     \<major>.\<minor>.\<patch>
    --
    -- 3.  Build version ARNs have all four nodes, and point to a specific
    --     build for a specific version of an object.
    Image -> 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.
    Image -> Maybe BuildType
buildType :: Prelude.Maybe BuildType,
    -- | The recipe that is used to create an Image Builder container image.
    Image -> Maybe ContainerRecipe
containerRecipe :: Prelude.Maybe ContainerRecipe,
    -- | The date on which this image was created.
    Image -> Maybe Text
dateCreated :: Prelude.Maybe Prelude.Text,
    -- | The distribution configuration used when creating this image.
    Image -> Maybe DistributionConfiguration
distributionConfiguration :: Prelude.Maybe DistributionConfiguration,
    -- | Collects additional information about the image being created, including
    -- the operating system (OS) version and package list. This information is
    -- used to enhance the overall experience of using EC2 Image Builder.
    -- Enabled by default.
    Image -> Maybe Bool
enhancedImageMetadataEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The image recipe used when creating the image.
    Image -> Maybe ImageRecipe
imageRecipe :: Prelude.Maybe ImageRecipe,
    -- | The image tests configuration used when creating this image.
    Image -> Maybe ImageTestsConfiguration
imageTestsConfiguration :: Prelude.Maybe ImageTestsConfiguration,
    -- | The infrastructure used when creating this image.
    Image -> Maybe InfrastructureConfiguration
infrastructureConfiguration :: Prelude.Maybe InfrastructureConfiguration,
    -- | The name of the image.
    Image -> 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.
    Image -> Maybe Text
osVersion :: Prelude.Maybe Prelude.Text,
    -- | The output resources produced when creating this image.
    Image -> Maybe OutputResources
outputResources :: Prelude.Maybe OutputResources,
    -- | The platform of the image.
    Image -> Maybe Platform
platform :: Prelude.Maybe Platform,
    -- | The Amazon Resource Name (ARN) of the image pipeline that created this
    -- image.
    Image -> Maybe Text
sourcePipelineArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the image pipeline that created this image.
    Image -> Maybe Text
sourcePipelineName :: Prelude.Maybe Prelude.Text,
    -- | The state of the image.
    Image -> Maybe ImageState
state :: Prelude.Maybe ImageState,
    -- | The tags of the image.
    Image -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Specifies whether this is an AMI or container image.
    Image -> Maybe ImageType
type' :: Prelude.Maybe ImageType,
    -- | The semantic version of the image.
    --
    -- The semantic version has four nodes:
    -- \<major>.\<minor>.\<patch>\/\<build>. You can assign values for the
    -- first three, and can filter on all of them.
    --
    -- __Assignment:__ For the first three nodes you can assign any positive
    -- integer value, including zero, with an upper limit of 2^30-1, or
    -- 1073741823 for each node. Image Builder automatically assigns the build
    -- number to the fourth node.
    --
    -- __Patterns:__ You can use any numeric pattern that adheres to the
    -- assignment requirements for the nodes that you can assign. For example,
    -- you might choose a software version pattern, such as 1.0.0, or a date,
    -- such as 2021.01.01.
    --
    -- __Filtering:__ With semantic versioning, you have the flexibility to use
    -- wildcards (x) to specify the most recent versions or nodes when
    -- selecting the base image or components for your recipe. When you use a
    -- wildcard in any node, all nodes to the right of the first wildcard must
    -- also be wildcards.
    Image -> Maybe Text
version :: Prelude.Maybe Prelude.Text
  }
  deriving (Image -> Image -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Image -> Image -> Bool
$c/= :: Image -> Image -> Bool
== :: Image -> Image -> Bool
$c== :: Image -> Image -> Bool
Prelude.Eq, ReadPrec [Image]
ReadPrec Image
Int -> ReadS Image
ReadS [Image]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Image]
$creadListPrec :: ReadPrec [Image]
readPrec :: ReadPrec Image
$creadPrec :: ReadPrec Image
readList :: ReadS [Image]
$creadList :: ReadS [Image]
readsPrec :: Int -> ReadS Image
$creadsPrec :: Int -> ReadS Image
Prelude.Read, Int -> Image -> ShowS
[Image] -> ShowS
Image -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Image] -> ShowS
$cshowList :: [Image] -> ShowS
show :: Image -> String
$cshow :: Image -> String
showsPrec :: Int -> Image -> ShowS
$cshowsPrec :: Int -> Image -> ShowS
Prelude.Show, forall x. Rep Image x -> Image
forall x. Image -> Rep Image x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Image x -> Image
$cfrom :: forall x. Image -> Rep Image x
Prelude.Generic)

-- |
-- Create a value of 'Image' 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', 'image_arn' - The Amazon Resource Name (ARN) of the image.
--
-- Semantic versioning is included in each object\'s Amazon Resource Name
-- (ARN), at the level that applies to that object as follows:
--
-- 1.  Versionless ARNs and Name ARNs do not include specific values in any
--     of the nodes. The nodes are either left off entirely, or they are
--     specified as wildcards, for example: x.x.x.
--
-- 2.  Version ARNs have only the first three nodes:
--     \<major>.\<minor>.\<patch>
--
-- 3.  Build version ARNs have all four nodes, and point to a specific
--     build for a specific version of an object.
--
-- 'buildType', 'image_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.
--
-- 'containerRecipe', 'image_containerRecipe' - The recipe that is used to create an Image Builder container image.
--
-- 'dateCreated', 'image_dateCreated' - The date on which this image was created.
--
-- 'distributionConfiguration', 'image_distributionConfiguration' - The distribution configuration used when creating this image.
--
-- 'enhancedImageMetadataEnabled', 'image_enhancedImageMetadataEnabled' - Collects additional information about the image being created, including
-- the operating system (OS) version and package list. This information is
-- used to enhance the overall experience of using EC2 Image Builder.
-- Enabled by default.
--
-- 'imageRecipe', 'image_imageRecipe' - The image recipe used when creating the image.
--
-- 'imageTestsConfiguration', 'image_imageTestsConfiguration' - The image tests configuration used when creating this image.
--
-- 'infrastructureConfiguration', 'image_infrastructureConfiguration' - The infrastructure used when creating this image.
--
-- 'name', 'image_name' - The name of the image.
--
-- 'osVersion', 'image_osVersion' - The operating system version of the instance. For example, Amazon Linux
-- 2, Ubuntu 18, or Microsoft Windows Server 2019.
--
-- 'outputResources', 'image_outputResources' - The output resources produced when creating this image.
--
-- 'platform', 'image_platform' - The platform of the image.
--
-- 'sourcePipelineArn', 'image_sourcePipelineArn' - The Amazon Resource Name (ARN) of the image pipeline that created this
-- image.
--
-- 'sourcePipelineName', 'image_sourcePipelineName' - The name of the image pipeline that created this image.
--
-- 'state', 'image_state' - The state of the image.
--
-- 'tags', 'image_tags' - The tags of the image.
--
-- 'type'', 'image_type' - Specifies whether this is an AMI or container image.
--
-- 'version', 'image_version' - The semantic version of the image.
--
-- The semantic version has four nodes:
-- \<major>.\<minor>.\<patch>\/\<build>. You can assign values for the
-- first three, and can filter on all of them.
--
-- __Assignment:__ For the first three nodes you can assign any positive
-- integer value, including zero, with an upper limit of 2^30-1, or
-- 1073741823 for each node. Image Builder automatically assigns the build
-- number to the fourth node.
--
-- __Patterns:__ You can use any numeric pattern that adheres to the
-- assignment requirements for the nodes that you can assign. For example,
-- you might choose a software version pattern, such as 1.0.0, or a date,
-- such as 2021.01.01.
--
-- __Filtering:__ With semantic versioning, you have the flexibility to use
-- wildcards (x) to specify the most recent versions or nodes when
-- selecting the base image or components for your recipe. When you use a
-- wildcard in any node, all nodes to the right of the first wildcard must
-- also be wildcards.
newImage ::
  Image
newImage :: Image
newImage =
  Image'
    { $sel:arn:Image' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:buildType:Image' :: Maybe BuildType
buildType = forall a. Maybe a
Prelude.Nothing,
      $sel:containerRecipe:Image' :: Maybe ContainerRecipe
containerRecipe = forall a. Maybe a
Prelude.Nothing,
      $sel:dateCreated:Image' :: Maybe Text
dateCreated = forall a. Maybe a
Prelude.Nothing,
      $sel:distributionConfiguration:Image' :: Maybe DistributionConfiguration
distributionConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:enhancedImageMetadataEnabled:Image' :: Maybe Bool
enhancedImageMetadataEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:imageRecipe:Image' :: Maybe ImageRecipe
imageRecipe = forall a. Maybe a
Prelude.Nothing,
      $sel:imageTestsConfiguration:Image' :: Maybe ImageTestsConfiguration
imageTestsConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:infrastructureConfiguration:Image' :: Maybe InfrastructureConfiguration
infrastructureConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:name:Image' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:osVersion:Image' :: Maybe Text
osVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:outputResources:Image' :: Maybe OutputResources
outputResources = forall a. Maybe a
Prelude.Nothing,
      $sel:platform:Image' :: Maybe Platform
platform = forall a. Maybe a
Prelude.Nothing,
      $sel:sourcePipelineArn:Image' :: Maybe Text
sourcePipelineArn = forall a. Maybe a
Prelude.Nothing,
      $sel:sourcePipelineName:Image' :: Maybe Text
sourcePipelineName = forall a. Maybe a
Prelude.Nothing,
      $sel:state:Image' :: Maybe ImageState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:Image' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:type':Image' :: Maybe ImageType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:version:Image' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the image.
--
-- Semantic versioning is included in each object\'s Amazon Resource Name
-- (ARN), at the level that applies to that object as follows:
--
-- 1.  Versionless ARNs and Name ARNs do not include specific values in any
--     of the nodes. The nodes are either left off entirely, or they are
--     specified as wildcards, for example: x.x.x.
--
-- 2.  Version ARNs have only the first three nodes:
--     \<major>.\<minor>.\<patch>
--
-- 3.  Build version ARNs have all four nodes, and point to a specific
--     build for a specific version of an object.
image_arn :: Lens.Lens' Image (Prelude.Maybe Prelude.Text)
image_arn :: Lens' Image (Maybe Text)
image_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe Text
arn :: Maybe Text
$sel:arn:Image' :: Image -> Maybe Text
arn} -> Maybe Text
arn) (\s :: Image
s@Image' {} Maybe Text
a -> Image
s {$sel:arn:Image' :: Maybe Text
arn = Maybe Text
a} :: Image)

-- | 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.
image_buildType :: Lens.Lens' Image (Prelude.Maybe BuildType)
image_buildType :: Lens' Image (Maybe BuildType)
image_buildType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe BuildType
buildType :: Maybe BuildType
$sel:buildType:Image' :: Image -> Maybe BuildType
buildType} -> Maybe BuildType
buildType) (\s :: Image
s@Image' {} Maybe BuildType
a -> Image
s {$sel:buildType:Image' :: Maybe BuildType
buildType = Maybe BuildType
a} :: Image)

-- | The recipe that is used to create an Image Builder container image.
image_containerRecipe :: Lens.Lens' Image (Prelude.Maybe ContainerRecipe)
image_containerRecipe :: Lens' Image (Maybe ContainerRecipe)
image_containerRecipe = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe ContainerRecipe
containerRecipe :: Maybe ContainerRecipe
$sel:containerRecipe:Image' :: Image -> Maybe ContainerRecipe
containerRecipe} -> Maybe ContainerRecipe
containerRecipe) (\s :: Image
s@Image' {} Maybe ContainerRecipe
a -> Image
s {$sel:containerRecipe:Image' :: Maybe ContainerRecipe
containerRecipe = Maybe ContainerRecipe
a} :: Image)

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

-- | The distribution configuration used when creating this image.
image_distributionConfiguration :: Lens.Lens' Image (Prelude.Maybe DistributionConfiguration)
image_distributionConfiguration :: Lens' Image (Maybe DistributionConfiguration)
image_distributionConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe DistributionConfiguration
distributionConfiguration :: Maybe DistributionConfiguration
$sel:distributionConfiguration:Image' :: Image -> Maybe DistributionConfiguration
distributionConfiguration} -> Maybe DistributionConfiguration
distributionConfiguration) (\s :: Image
s@Image' {} Maybe DistributionConfiguration
a -> Image
s {$sel:distributionConfiguration:Image' :: Maybe DistributionConfiguration
distributionConfiguration = Maybe DistributionConfiguration
a} :: Image)

-- | Collects additional information about the image being created, including
-- the operating system (OS) version and package list. This information is
-- used to enhance the overall experience of using EC2 Image Builder.
-- Enabled by default.
image_enhancedImageMetadataEnabled :: Lens.Lens' Image (Prelude.Maybe Prelude.Bool)
image_enhancedImageMetadataEnabled :: Lens' Image (Maybe Bool)
image_enhancedImageMetadataEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe Bool
enhancedImageMetadataEnabled :: Maybe Bool
$sel:enhancedImageMetadataEnabled:Image' :: Image -> Maybe Bool
enhancedImageMetadataEnabled} -> Maybe Bool
enhancedImageMetadataEnabled) (\s :: Image
s@Image' {} Maybe Bool
a -> Image
s {$sel:enhancedImageMetadataEnabled:Image' :: Maybe Bool
enhancedImageMetadataEnabled = Maybe Bool
a} :: Image)

-- | The image recipe used when creating the image.
image_imageRecipe :: Lens.Lens' Image (Prelude.Maybe ImageRecipe)
image_imageRecipe :: Lens' Image (Maybe ImageRecipe)
image_imageRecipe = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe ImageRecipe
imageRecipe :: Maybe ImageRecipe
$sel:imageRecipe:Image' :: Image -> Maybe ImageRecipe
imageRecipe} -> Maybe ImageRecipe
imageRecipe) (\s :: Image
s@Image' {} Maybe ImageRecipe
a -> Image
s {$sel:imageRecipe:Image' :: Maybe ImageRecipe
imageRecipe = Maybe ImageRecipe
a} :: Image)

-- | The image tests configuration used when creating this image.
image_imageTestsConfiguration :: Lens.Lens' Image (Prelude.Maybe ImageTestsConfiguration)
image_imageTestsConfiguration :: Lens' Image (Maybe ImageTestsConfiguration)
image_imageTestsConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe ImageTestsConfiguration
imageTestsConfiguration :: Maybe ImageTestsConfiguration
$sel:imageTestsConfiguration:Image' :: Image -> Maybe ImageTestsConfiguration
imageTestsConfiguration} -> Maybe ImageTestsConfiguration
imageTestsConfiguration) (\s :: Image
s@Image' {} Maybe ImageTestsConfiguration
a -> Image
s {$sel:imageTestsConfiguration:Image' :: Maybe ImageTestsConfiguration
imageTestsConfiguration = Maybe ImageTestsConfiguration
a} :: Image)

-- | The infrastructure used when creating this image.
image_infrastructureConfiguration :: Lens.Lens' Image (Prelude.Maybe InfrastructureConfiguration)
image_infrastructureConfiguration :: Lens' Image (Maybe InfrastructureConfiguration)
image_infrastructureConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe InfrastructureConfiguration
infrastructureConfiguration :: Maybe InfrastructureConfiguration
$sel:infrastructureConfiguration:Image' :: Image -> Maybe InfrastructureConfiguration
infrastructureConfiguration} -> Maybe InfrastructureConfiguration
infrastructureConfiguration) (\s :: Image
s@Image' {} Maybe InfrastructureConfiguration
a -> Image
s {$sel:infrastructureConfiguration:Image' :: Maybe InfrastructureConfiguration
infrastructureConfiguration = Maybe InfrastructureConfiguration
a} :: Image)

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

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

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

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

-- | The Amazon Resource Name (ARN) of the image pipeline that created this
-- image.
image_sourcePipelineArn :: Lens.Lens' Image (Prelude.Maybe Prelude.Text)
image_sourcePipelineArn :: Lens' Image (Maybe Text)
image_sourcePipelineArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe Text
sourcePipelineArn :: Maybe Text
$sel:sourcePipelineArn:Image' :: Image -> Maybe Text
sourcePipelineArn} -> Maybe Text
sourcePipelineArn) (\s :: Image
s@Image' {} Maybe Text
a -> Image
s {$sel:sourcePipelineArn:Image' :: Maybe Text
sourcePipelineArn = Maybe Text
a} :: Image)

-- | The name of the image pipeline that created this image.
image_sourcePipelineName :: Lens.Lens' Image (Prelude.Maybe Prelude.Text)
image_sourcePipelineName :: Lens' Image (Maybe Text)
image_sourcePipelineName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe Text
sourcePipelineName :: Maybe Text
$sel:sourcePipelineName:Image' :: Image -> Maybe Text
sourcePipelineName} -> Maybe Text
sourcePipelineName) (\s :: Image
s@Image' {} Maybe Text
a -> Image
s {$sel:sourcePipelineName:Image' :: Maybe Text
sourcePipelineName = Maybe Text
a} :: Image)

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

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

-- | The semantic version of the image.
--
-- The semantic version has four nodes:
-- \<major>.\<minor>.\<patch>\/\<build>. You can assign values for the
-- first three, and can filter on all of them.
--
-- __Assignment:__ For the first three nodes you can assign any positive
-- integer value, including zero, with an upper limit of 2^30-1, or
-- 1073741823 for each node. Image Builder automatically assigns the build
-- number to the fourth node.
--
-- __Patterns:__ You can use any numeric pattern that adheres to the
-- assignment requirements for the nodes that you can assign. For example,
-- you might choose a software version pattern, such as 1.0.0, or a date,
-- such as 2021.01.01.
--
-- __Filtering:__ With semantic versioning, you have the flexibility to use
-- wildcards (x) to specify the most recent versions or nodes when
-- selecting the base image or components for your recipe. When you use a
-- wildcard in any node, all nodes to the right of the first wildcard must
-- also be wildcards.
image_version :: Lens.Lens' Image (Prelude.Maybe Prelude.Text)
image_version :: Lens' Image (Maybe Text)
image_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Image' {Maybe Text
version :: Maybe Text
$sel:version:Image' :: Image -> Maybe Text
version} -> Maybe Text
version) (\s :: Image
s@Image' {} Maybe Text
a -> Image
s {$sel:version:Image' :: Maybe Text
version = Maybe Text
a} :: Image)

instance Data.FromJSON Image where
  parseJSON :: Value -> Parser Image
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Image"
      ( \Object
x ->
          Maybe Text
-> Maybe BuildType
-> Maybe ContainerRecipe
-> Maybe Text
-> Maybe DistributionConfiguration
-> Maybe Bool
-> Maybe ImageRecipe
-> Maybe ImageTestsConfiguration
-> Maybe InfrastructureConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe OutputResources
-> Maybe Platform
-> Maybe Text
-> Maybe Text
-> Maybe ImageState
-> Maybe (HashMap Text Text)
-> Maybe ImageType
-> Maybe Text
-> Image
Image'
            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
"containerRecipe")
            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
"distributionConfiguration")
            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
"enhancedImageMetadataEnabled")
            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
"imageRecipe")
            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
"imageTestsConfiguration")
            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
"infrastructureConfiguration")
            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
"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
"sourcePipelineArn")
            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
"sourcePipelineName")
            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 Image where
  hashWithSalt :: Int -> Image -> Int
hashWithSalt Int
_salt Image' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe BuildType
Maybe ImageState
Maybe ImageTestsConfiguration
Maybe ImageType
Maybe OutputResources
Maybe Platform
Maybe InfrastructureConfiguration
Maybe ImageRecipe
Maybe ContainerRecipe
Maybe DistributionConfiguration
version :: Maybe Text
type' :: Maybe ImageType
tags :: Maybe (HashMap Text Text)
state :: Maybe ImageState
sourcePipelineName :: Maybe Text
sourcePipelineArn :: Maybe Text
platform :: Maybe Platform
outputResources :: Maybe OutputResources
osVersion :: Maybe Text
name :: Maybe Text
infrastructureConfiguration :: Maybe InfrastructureConfiguration
imageTestsConfiguration :: Maybe ImageTestsConfiguration
imageRecipe :: Maybe ImageRecipe
enhancedImageMetadataEnabled :: Maybe Bool
distributionConfiguration :: Maybe DistributionConfiguration
dateCreated :: Maybe Text
containerRecipe :: Maybe ContainerRecipe
buildType :: Maybe BuildType
arn :: Maybe Text
$sel:version:Image' :: Image -> Maybe Text
$sel:type':Image' :: Image -> Maybe ImageType
$sel:tags:Image' :: Image -> Maybe (HashMap Text Text)
$sel:state:Image' :: Image -> Maybe ImageState
$sel:sourcePipelineName:Image' :: Image -> Maybe Text
$sel:sourcePipelineArn:Image' :: Image -> Maybe Text
$sel:platform:Image' :: Image -> Maybe Platform
$sel:outputResources:Image' :: Image -> Maybe OutputResources
$sel:osVersion:Image' :: Image -> Maybe Text
$sel:name:Image' :: Image -> Maybe Text
$sel:infrastructureConfiguration:Image' :: Image -> Maybe InfrastructureConfiguration
$sel:imageTestsConfiguration:Image' :: Image -> Maybe ImageTestsConfiguration
$sel:imageRecipe:Image' :: Image -> Maybe ImageRecipe
$sel:enhancedImageMetadataEnabled:Image' :: Image -> Maybe Bool
$sel:distributionConfiguration:Image' :: Image -> Maybe DistributionConfiguration
$sel:dateCreated:Image' :: Image -> Maybe Text
$sel:containerRecipe:Image' :: Image -> Maybe ContainerRecipe
$sel:buildType:Image' :: Image -> Maybe BuildType
$sel:arn:Image' :: Image -> 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 ContainerRecipe
containerRecipe
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dateCreated
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DistributionConfiguration
distributionConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enhancedImageMetadataEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ImageRecipe
imageRecipe
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ImageTestsConfiguration
imageTestsConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InfrastructureConfiguration
infrastructureConfiguration
      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 Platform
platform
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourcePipelineArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourcePipelineName
      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 Image where
  rnf :: Image -> ()
rnf Image' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe BuildType
Maybe ImageState
Maybe ImageTestsConfiguration
Maybe ImageType
Maybe OutputResources
Maybe Platform
Maybe InfrastructureConfiguration
Maybe ImageRecipe
Maybe ContainerRecipe
Maybe DistributionConfiguration
version :: Maybe Text
type' :: Maybe ImageType
tags :: Maybe (HashMap Text Text)
state :: Maybe ImageState
sourcePipelineName :: Maybe Text
sourcePipelineArn :: Maybe Text
platform :: Maybe Platform
outputResources :: Maybe OutputResources
osVersion :: Maybe Text
name :: Maybe Text
infrastructureConfiguration :: Maybe InfrastructureConfiguration
imageTestsConfiguration :: Maybe ImageTestsConfiguration
imageRecipe :: Maybe ImageRecipe
enhancedImageMetadataEnabled :: Maybe Bool
distributionConfiguration :: Maybe DistributionConfiguration
dateCreated :: Maybe Text
containerRecipe :: Maybe ContainerRecipe
buildType :: Maybe BuildType
arn :: Maybe Text
$sel:version:Image' :: Image -> Maybe Text
$sel:type':Image' :: Image -> Maybe ImageType
$sel:tags:Image' :: Image -> Maybe (HashMap Text Text)
$sel:state:Image' :: Image -> Maybe ImageState
$sel:sourcePipelineName:Image' :: Image -> Maybe Text
$sel:sourcePipelineArn:Image' :: Image -> Maybe Text
$sel:platform:Image' :: Image -> Maybe Platform
$sel:outputResources:Image' :: Image -> Maybe OutputResources
$sel:osVersion:Image' :: Image -> Maybe Text
$sel:name:Image' :: Image -> Maybe Text
$sel:infrastructureConfiguration:Image' :: Image -> Maybe InfrastructureConfiguration
$sel:imageTestsConfiguration:Image' :: Image -> Maybe ImageTestsConfiguration
$sel:imageRecipe:Image' :: Image -> Maybe ImageRecipe
$sel:enhancedImageMetadataEnabled:Image' :: Image -> Maybe Bool
$sel:distributionConfiguration:Image' :: Image -> Maybe DistributionConfiguration
$sel:dateCreated:Image' :: Image -> Maybe Text
$sel:containerRecipe:Image' :: Image -> Maybe ContainerRecipe
$sel:buildType:Image' :: Image -> Maybe BuildType
$sel:arn:Image' :: Image -> 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 ContainerRecipe
containerRecipe
      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 DistributionConfiguration
distributionConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enhancedImageMetadataEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImageRecipe
imageRecipe
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImageTestsConfiguration
imageTestsConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InfrastructureConfiguration
infrastructureConfiguration
      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 Platform
platform
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourcePipelineArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourcePipelineName
      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