{-# 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.SSM.Types.DocumentDescription
-- 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.SSM.Types.DocumentDescription where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.SSM.Types.AttachmentInformation
import Amazonka.SSM.Types.DocumentFormat
import Amazonka.SSM.Types.DocumentHashType
import Amazonka.SSM.Types.DocumentParameter
import Amazonka.SSM.Types.DocumentRequires
import Amazonka.SSM.Types.DocumentStatus
import Amazonka.SSM.Types.DocumentType
import Amazonka.SSM.Types.PlatformType
import Amazonka.SSM.Types.ReviewInformation
import Amazonka.SSM.Types.ReviewStatus
import Amazonka.SSM.Types.Tag

-- | Describes an Amazon Web Services Systems Manager document (SSM
-- document).
--
-- /See:/ 'newDocumentDescription' smart constructor.
data DocumentDescription = DocumentDescription'
  { -- | The version of the document currently approved for use in the
    -- organization.
    DocumentDescription -> Maybe Text
approvedVersion :: Prelude.Maybe Prelude.Text,
    -- | Details about the document attachments, including names, locations,
    -- sizes, and so on.
    DocumentDescription -> Maybe [AttachmentInformation]
attachmentsInformation :: Prelude.Maybe [AttachmentInformation],
    -- | The user in your organization who created the document.
    DocumentDescription -> Maybe Text
author :: Prelude.Maybe Prelude.Text,
    -- | The classification of a document to help you identify and categorize its
    -- use.
    DocumentDescription -> Maybe [Text]
category :: Prelude.Maybe [Prelude.Text],
    -- | The value that identifies a document\'s category.
    DocumentDescription -> Maybe [Text]
categoryEnum :: Prelude.Maybe [Prelude.Text],
    -- | The date when the document was created.
    DocumentDescription -> Maybe POSIX
createdDate :: Prelude.Maybe Data.POSIX,
    -- | The default version.
    DocumentDescription -> Maybe Text
defaultVersion :: Prelude.Maybe Prelude.Text,
    -- | A description of the document.
    DocumentDescription -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The friendly name of the SSM document. This value can differ for each
    -- version of the document. If you want to update this value, see
    -- UpdateDocument.
    DocumentDescription -> Maybe Text
displayName :: Prelude.Maybe Prelude.Text,
    -- | The document format, either JSON or YAML.
    DocumentDescription -> Maybe DocumentFormat
documentFormat :: Prelude.Maybe DocumentFormat,
    -- | The type of document.
    DocumentDescription -> Maybe DocumentType
documentType :: Prelude.Maybe DocumentType,
    -- | The document version.
    DocumentDescription -> Maybe Text
documentVersion :: Prelude.Maybe Prelude.Text,
    -- | The Sha256 or Sha1 hash created by the system when the document was
    -- created.
    --
    -- Sha1 hashes have been deprecated.
    DocumentDescription -> Maybe Text
hash :: Prelude.Maybe Prelude.Text,
    -- | The hash type of the document. Valid values include @Sha256@ or @Sha1@.
    --
    -- Sha1 hashes have been deprecated.
    DocumentDescription -> Maybe DocumentHashType
hashType :: Prelude.Maybe DocumentHashType,
    -- | The latest version of the document.
    DocumentDescription -> Maybe Text
latestVersion :: Prelude.Maybe Prelude.Text,
    -- | The name of the SSM document.
    DocumentDescription -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services user account that created the document.
    DocumentDescription -> Maybe Text
owner :: Prelude.Maybe Prelude.Text,
    -- | A description of the parameters for a document.
    DocumentDescription -> Maybe [DocumentParameter]
parameters :: Prelude.Maybe [DocumentParameter],
    -- | The version of the document that is currently under review.
    DocumentDescription -> Maybe Text
pendingReviewVersion :: Prelude.Maybe Prelude.Text,
    -- | The list of operating system (OS) platforms compatible with this SSM
    -- document.
    DocumentDescription -> Maybe [PlatformType]
platformTypes :: Prelude.Maybe [PlatformType],
    -- | A list of SSM documents required by a document. For example, an
    -- @ApplicationConfiguration@ document requires an
    -- @ApplicationConfigurationSchema@ document.
    DocumentDescription -> Maybe (NonEmpty DocumentRequires)
requires :: Prelude.Maybe (Prelude.NonEmpty DocumentRequires),
    -- | Details about the review of a document.
    DocumentDescription -> Maybe (NonEmpty ReviewInformation)
reviewInformation :: Prelude.Maybe (Prelude.NonEmpty ReviewInformation),
    -- | The current status of the review.
    DocumentDescription -> Maybe ReviewStatus
reviewStatus :: Prelude.Maybe ReviewStatus,
    -- | The schema version.
    DocumentDescription -> Maybe Text
schemaVersion :: Prelude.Maybe Prelude.Text,
    -- | The SHA1 hash of the document, which you can use for verification.
    DocumentDescription -> Maybe Text
sha1 :: Prelude.Maybe Prelude.Text,
    -- | The status of the SSM document.
    DocumentDescription -> Maybe DocumentStatus
status :: Prelude.Maybe DocumentStatus,
    -- | A message returned by Amazon Web Services Systems Manager that explains
    -- the @Status@ value. For example, a @Failed@ status might be explained by
    -- the @StatusInformation@ message, \"The specified S3 bucket doesn\'t
    -- exist. Verify that the URL of the S3 bucket is correct.\"
    DocumentDescription -> Maybe Text
statusInformation :: Prelude.Maybe Prelude.Text,
    -- | The tags, or metadata, that have been applied to the document.
    DocumentDescription -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The target type which defines the kinds of resources the document can
    -- run on. For example, @\/AWS::EC2::Instance@. For a list of valid
    -- resource types, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-template-resource-type-ref.html Amazon Web Services resource and property types reference>
    -- in the /CloudFormation User Guide/.
    DocumentDescription -> Maybe Text
targetType :: Prelude.Maybe Prelude.Text,
    -- | The version of the artifact associated with the document.
    DocumentDescription -> Maybe Text
versionName :: Prelude.Maybe Prelude.Text
  }
  deriving (DocumentDescription -> DocumentDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DocumentDescription -> DocumentDescription -> Bool
$c/= :: DocumentDescription -> DocumentDescription -> Bool
== :: DocumentDescription -> DocumentDescription -> Bool
$c== :: DocumentDescription -> DocumentDescription -> Bool
Prelude.Eq, ReadPrec [DocumentDescription]
ReadPrec DocumentDescription
Int -> ReadS DocumentDescription
ReadS [DocumentDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DocumentDescription]
$creadListPrec :: ReadPrec [DocumentDescription]
readPrec :: ReadPrec DocumentDescription
$creadPrec :: ReadPrec DocumentDescription
readList :: ReadS [DocumentDescription]
$creadList :: ReadS [DocumentDescription]
readsPrec :: Int -> ReadS DocumentDescription
$creadsPrec :: Int -> ReadS DocumentDescription
Prelude.Read, Int -> DocumentDescription -> ShowS
[DocumentDescription] -> ShowS
DocumentDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DocumentDescription] -> ShowS
$cshowList :: [DocumentDescription] -> ShowS
show :: DocumentDescription -> String
$cshow :: DocumentDescription -> String
showsPrec :: Int -> DocumentDescription -> ShowS
$cshowsPrec :: Int -> DocumentDescription -> ShowS
Prelude.Show, forall x. Rep DocumentDescription x -> DocumentDescription
forall x. DocumentDescription -> Rep DocumentDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DocumentDescription x -> DocumentDescription
$cfrom :: forall x. DocumentDescription -> Rep DocumentDescription x
Prelude.Generic)

-- |
-- Create a value of 'DocumentDescription' 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:
--
-- 'approvedVersion', 'documentDescription_approvedVersion' - The version of the document currently approved for use in the
-- organization.
--
-- 'attachmentsInformation', 'documentDescription_attachmentsInformation' - Details about the document attachments, including names, locations,
-- sizes, and so on.
--
-- 'author', 'documentDescription_author' - The user in your organization who created the document.
--
-- 'category', 'documentDescription_category' - The classification of a document to help you identify and categorize its
-- use.
--
-- 'categoryEnum', 'documentDescription_categoryEnum' - The value that identifies a document\'s category.
--
-- 'createdDate', 'documentDescription_createdDate' - The date when the document was created.
--
-- 'defaultVersion', 'documentDescription_defaultVersion' - The default version.
--
-- 'description', 'documentDescription_description' - A description of the document.
--
-- 'displayName', 'documentDescription_displayName' - The friendly name of the SSM document. This value can differ for each
-- version of the document. If you want to update this value, see
-- UpdateDocument.
--
-- 'documentFormat', 'documentDescription_documentFormat' - The document format, either JSON or YAML.
--
-- 'documentType', 'documentDescription_documentType' - The type of document.
--
-- 'documentVersion', 'documentDescription_documentVersion' - The document version.
--
-- 'hash', 'documentDescription_hash' - The Sha256 or Sha1 hash created by the system when the document was
-- created.
--
-- Sha1 hashes have been deprecated.
--
-- 'hashType', 'documentDescription_hashType' - The hash type of the document. Valid values include @Sha256@ or @Sha1@.
--
-- Sha1 hashes have been deprecated.
--
-- 'latestVersion', 'documentDescription_latestVersion' - The latest version of the document.
--
-- 'name', 'documentDescription_name' - The name of the SSM document.
--
-- 'owner', 'documentDescription_owner' - The Amazon Web Services user account that created the document.
--
-- 'parameters', 'documentDescription_parameters' - A description of the parameters for a document.
--
-- 'pendingReviewVersion', 'documentDescription_pendingReviewVersion' - The version of the document that is currently under review.
--
-- 'platformTypes', 'documentDescription_platformTypes' - The list of operating system (OS) platforms compatible with this SSM
-- document.
--
-- 'requires', 'documentDescription_requires' - A list of SSM documents required by a document. For example, an
-- @ApplicationConfiguration@ document requires an
-- @ApplicationConfigurationSchema@ document.
--
-- 'reviewInformation', 'documentDescription_reviewInformation' - Details about the review of a document.
--
-- 'reviewStatus', 'documentDescription_reviewStatus' - The current status of the review.
--
-- 'schemaVersion', 'documentDescription_schemaVersion' - The schema version.
--
-- 'sha1', 'documentDescription_sha1' - The SHA1 hash of the document, which you can use for verification.
--
-- 'status', 'documentDescription_status' - The status of the SSM document.
--
-- 'statusInformation', 'documentDescription_statusInformation' - A message returned by Amazon Web Services Systems Manager that explains
-- the @Status@ value. For example, a @Failed@ status might be explained by
-- the @StatusInformation@ message, \"The specified S3 bucket doesn\'t
-- exist. Verify that the URL of the S3 bucket is correct.\"
--
-- 'tags', 'documentDescription_tags' - The tags, or metadata, that have been applied to the document.
--
-- 'targetType', 'documentDescription_targetType' - The target type which defines the kinds of resources the document can
-- run on. For example, @\/AWS::EC2::Instance@. For a list of valid
-- resource types, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-template-resource-type-ref.html Amazon Web Services resource and property types reference>
-- in the /CloudFormation User Guide/.
--
-- 'versionName', 'documentDescription_versionName' - The version of the artifact associated with the document.
newDocumentDescription ::
  DocumentDescription
newDocumentDescription :: DocumentDescription
newDocumentDescription =
  DocumentDescription'
    { $sel:approvedVersion:DocumentDescription' :: Maybe Text
approvedVersion =
        forall a. Maybe a
Prelude.Nothing,
      $sel:attachmentsInformation:DocumentDescription' :: Maybe [AttachmentInformation]
attachmentsInformation = forall a. Maybe a
Prelude.Nothing,
      $sel:author:DocumentDescription' :: Maybe Text
author = forall a. Maybe a
Prelude.Nothing,
      $sel:category:DocumentDescription' :: Maybe [Text]
category = forall a. Maybe a
Prelude.Nothing,
      $sel:categoryEnum:DocumentDescription' :: Maybe [Text]
categoryEnum = forall a. Maybe a
Prelude.Nothing,
      $sel:createdDate:DocumentDescription' :: Maybe POSIX
createdDate = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultVersion:DocumentDescription' :: Maybe Text
defaultVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:description:DocumentDescription' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:displayName:DocumentDescription' :: Maybe Text
displayName = forall a. Maybe a
Prelude.Nothing,
      $sel:documentFormat:DocumentDescription' :: Maybe DocumentFormat
documentFormat = forall a. Maybe a
Prelude.Nothing,
      $sel:documentType:DocumentDescription' :: Maybe DocumentType
documentType = forall a. Maybe a
Prelude.Nothing,
      $sel:documentVersion:DocumentDescription' :: Maybe Text
documentVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:hash:DocumentDescription' :: Maybe Text
hash = forall a. Maybe a
Prelude.Nothing,
      $sel:hashType:DocumentDescription' :: Maybe DocumentHashType
hashType = forall a. Maybe a
Prelude.Nothing,
      $sel:latestVersion:DocumentDescription' :: Maybe Text
latestVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DocumentDescription' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:owner:DocumentDescription' :: Maybe Text
owner = forall a. Maybe a
Prelude.Nothing,
      $sel:parameters:DocumentDescription' :: Maybe [DocumentParameter]
parameters = forall a. Maybe a
Prelude.Nothing,
      $sel:pendingReviewVersion:DocumentDescription' :: Maybe Text
pendingReviewVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:platformTypes:DocumentDescription' :: Maybe [PlatformType]
platformTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:requires:DocumentDescription' :: Maybe (NonEmpty DocumentRequires)
requires = forall a. Maybe a
Prelude.Nothing,
      $sel:reviewInformation:DocumentDescription' :: Maybe (NonEmpty ReviewInformation)
reviewInformation = forall a. Maybe a
Prelude.Nothing,
      $sel:reviewStatus:DocumentDescription' :: Maybe ReviewStatus
reviewStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:schemaVersion:DocumentDescription' :: Maybe Text
schemaVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:sha1:DocumentDescription' :: Maybe Text
sha1 = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DocumentDescription' :: Maybe DocumentStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusInformation:DocumentDescription' :: Maybe Text
statusInformation = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:DocumentDescription' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:targetType:DocumentDescription' :: Maybe Text
targetType = forall a. Maybe a
Prelude.Nothing,
      $sel:versionName:DocumentDescription' :: Maybe Text
versionName = forall a. Maybe a
Prelude.Nothing
    }

-- | The version of the document currently approved for use in the
-- organization.
documentDescription_approvedVersion :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_approvedVersion :: Lens' DocumentDescription (Maybe Text)
documentDescription_approvedVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
approvedVersion :: Maybe Text
$sel:approvedVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
approvedVersion} -> Maybe Text
approvedVersion) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:approvedVersion:DocumentDescription' :: Maybe Text
approvedVersion = Maybe Text
a} :: DocumentDescription)

-- | Details about the document attachments, including names, locations,
-- sizes, and so on.
documentDescription_attachmentsInformation :: Lens.Lens' DocumentDescription (Prelude.Maybe [AttachmentInformation])
documentDescription_attachmentsInformation :: Lens' DocumentDescription (Maybe [AttachmentInformation])
documentDescription_attachmentsInformation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe [AttachmentInformation]
attachmentsInformation :: Maybe [AttachmentInformation]
$sel:attachmentsInformation:DocumentDescription' :: DocumentDescription -> Maybe [AttachmentInformation]
attachmentsInformation} -> Maybe [AttachmentInformation]
attachmentsInformation) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe [AttachmentInformation]
a -> DocumentDescription
s {$sel:attachmentsInformation:DocumentDescription' :: Maybe [AttachmentInformation]
attachmentsInformation = Maybe [AttachmentInformation]
a} :: DocumentDescription) 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 user in your organization who created the document.
documentDescription_author :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_author :: Lens' DocumentDescription (Maybe Text)
documentDescription_author = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
author :: Maybe Text
$sel:author:DocumentDescription' :: DocumentDescription -> Maybe Text
author} -> Maybe Text
author) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:author:DocumentDescription' :: Maybe Text
author = Maybe Text
a} :: DocumentDescription)

-- | The classification of a document to help you identify and categorize its
-- use.
documentDescription_category :: Lens.Lens' DocumentDescription (Prelude.Maybe [Prelude.Text])
documentDescription_category :: Lens' DocumentDescription (Maybe [Text])
documentDescription_category = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe [Text]
category :: Maybe [Text]
$sel:category:DocumentDescription' :: DocumentDescription -> Maybe [Text]
category} -> Maybe [Text]
category) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe [Text]
a -> DocumentDescription
s {$sel:category:DocumentDescription' :: Maybe [Text]
category = Maybe [Text]
a} :: DocumentDescription) 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 value that identifies a document\'s category.
documentDescription_categoryEnum :: Lens.Lens' DocumentDescription (Prelude.Maybe [Prelude.Text])
documentDescription_categoryEnum :: Lens' DocumentDescription (Maybe [Text])
documentDescription_categoryEnum = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe [Text]
categoryEnum :: Maybe [Text]
$sel:categoryEnum:DocumentDescription' :: DocumentDescription -> Maybe [Text]
categoryEnum} -> Maybe [Text]
categoryEnum) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe [Text]
a -> DocumentDescription
s {$sel:categoryEnum:DocumentDescription' :: Maybe [Text]
categoryEnum = Maybe [Text]
a} :: DocumentDescription) 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 date when the document was created.
documentDescription_createdDate :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.UTCTime)
documentDescription_createdDate :: Lens' DocumentDescription (Maybe UTCTime)
documentDescription_createdDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe POSIX
createdDate :: Maybe POSIX
$sel:createdDate:DocumentDescription' :: DocumentDescription -> Maybe POSIX
createdDate} -> Maybe POSIX
createdDate) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe POSIX
a -> DocumentDescription
s {$sel:createdDate:DocumentDescription' :: Maybe POSIX
createdDate = Maybe POSIX
a} :: DocumentDescription) 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

-- | The default version.
documentDescription_defaultVersion :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_defaultVersion :: Lens' DocumentDescription (Maybe Text)
documentDescription_defaultVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
defaultVersion :: Maybe Text
$sel:defaultVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
defaultVersion} -> Maybe Text
defaultVersion) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:defaultVersion:DocumentDescription' :: Maybe Text
defaultVersion = Maybe Text
a} :: DocumentDescription)

-- | A description of the document.
documentDescription_description :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_description :: Lens' DocumentDescription (Maybe Text)
documentDescription_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
description :: Maybe Text
$sel:description:DocumentDescription' :: DocumentDescription -> Maybe Text
description} -> Maybe Text
description) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:description:DocumentDescription' :: Maybe Text
description = Maybe Text
a} :: DocumentDescription)

-- | The friendly name of the SSM document. This value can differ for each
-- version of the document. If you want to update this value, see
-- UpdateDocument.
documentDescription_displayName :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_displayName :: Lens' DocumentDescription (Maybe Text)
documentDescription_displayName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
displayName :: Maybe Text
$sel:displayName:DocumentDescription' :: DocumentDescription -> Maybe Text
displayName} -> Maybe Text
displayName) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:displayName:DocumentDescription' :: Maybe Text
displayName = Maybe Text
a} :: DocumentDescription)

-- | The document format, either JSON or YAML.
documentDescription_documentFormat :: Lens.Lens' DocumentDescription (Prelude.Maybe DocumentFormat)
documentDescription_documentFormat :: Lens' DocumentDescription (Maybe DocumentFormat)
documentDescription_documentFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe DocumentFormat
documentFormat :: Maybe DocumentFormat
$sel:documentFormat:DocumentDescription' :: DocumentDescription -> Maybe DocumentFormat
documentFormat} -> Maybe DocumentFormat
documentFormat) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe DocumentFormat
a -> DocumentDescription
s {$sel:documentFormat:DocumentDescription' :: Maybe DocumentFormat
documentFormat = Maybe DocumentFormat
a} :: DocumentDescription)

-- | The type of document.
documentDescription_documentType :: Lens.Lens' DocumentDescription (Prelude.Maybe DocumentType)
documentDescription_documentType :: Lens' DocumentDescription (Maybe DocumentType)
documentDescription_documentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe DocumentType
documentType :: Maybe DocumentType
$sel:documentType:DocumentDescription' :: DocumentDescription -> Maybe DocumentType
documentType} -> Maybe DocumentType
documentType) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe DocumentType
a -> DocumentDescription
s {$sel:documentType:DocumentDescription' :: Maybe DocumentType
documentType = Maybe DocumentType
a} :: DocumentDescription)

-- | The document version.
documentDescription_documentVersion :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_documentVersion :: Lens' DocumentDescription (Maybe Text)
documentDescription_documentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
documentVersion :: Maybe Text
$sel:documentVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
documentVersion} -> Maybe Text
documentVersion) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:documentVersion:DocumentDescription' :: Maybe Text
documentVersion = Maybe Text
a} :: DocumentDescription)

-- | The Sha256 or Sha1 hash created by the system when the document was
-- created.
--
-- Sha1 hashes have been deprecated.
documentDescription_hash :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_hash :: Lens' DocumentDescription (Maybe Text)
documentDescription_hash = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
hash :: Maybe Text
$sel:hash:DocumentDescription' :: DocumentDescription -> Maybe Text
hash} -> Maybe Text
hash) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:hash:DocumentDescription' :: Maybe Text
hash = Maybe Text
a} :: DocumentDescription)

-- | The hash type of the document. Valid values include @Sha256@ or @Sha1@.
--
-- Sha1 hashes have been deprecated.
documentDescription_hashType :: Lens.Lens' DocumentDescription (Prelude.Maybe DocumentHashType)
documentDescription_hashType :: Lens' DocumentDescription (Maybe DocumentHashType)
documentDescription_hashType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe DocumentHashType
hashType :: Maybe DocumentHashType
$sel:hashType:DocumentDescription' :: DocumentDescription -> Maybe DocumentHashType
hashType} -> Maybe DocumentHashType
hashType) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe DocumentHashType
a -> DocumentDescription
s {$sel:hashType:DocumentDescription' :: Maybe DocumentHashType
hashType = Maybe DocumentHashType
a} :: DocumentDescription)

-- | The latest version of the document.
documentDescription_latestVersion :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_latestVersion :: Lens' DocumentDescription (Maybe Text)
documentDescription_latestVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
latestVersion :: Maybe Text
$sel:latestVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
latestVersion} -> Maybe Text
latestVersion) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:latestVersion:DocumentDescription' :: Maybe Text
latestVersion = Maybe Text
a} :: DocumentDescription)

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

-- | The Amazon Web Services user account that created the document.
documentDescription_owner :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_owner :: Lens' DocumentDescription (Maybe Text)
documentDescription_owner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
owner :: Maybe Text
$sel:owner:DocumentDescription' :: DocumentDescription -> Maybe Text
owner} -> Maybe Text
owner) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:owner:DocumentDescription' :: Maybe Text
owner = Maybe Text
a} :: DocumentDescription)

-- | A description of the parameters for a document.
documentDescription_parameters :: Lens.Lens' DocumentDescription (Prelude.Maybe [DocumentParameter])
documentDescription_parameters :: Lens' DocumentDescription (Maybe [DocumentParameter])
documentDescription_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe [DocumentParameter]
parameters :: Maybe [DocumentParameter]
$sel:parameters:DocumentDescription' :: DocumentDescription -> Maybe [DocumentParameter]
parameters} -> Maybe [DocumentParameter]
parameters) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe [DocumentParameter]
a -> DocumentDescription
s {$sel:parameters:DocumentDescription' :: Maybe [DocumentParameter]
parameters = Maybe [DocumentParameter]
a} :: DocumentDescription) 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 version of the document that is currently under review.
documentDescription_pendingReviewVersion :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_pendingReviewVersion :: Lens' DocumentDescription (Maybe Text)
documentDescription_pendingReviewVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
pendingReviewVersion :: Maybe Text
$sel:pendingReviewVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
pendingReviewVersion} -> Maybe Text
pendingReviewVersion) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:pendingReviewVersion:DocumentDescription' :: Maybe Text
pendingReviewVersion = Maybe Text
a} :: DocumentDescription)

-- | The list of operating system (OS) platforms compatible with this SSM
-- document.
documentDescription_platformTypes :: Lens.Lens' DocumentDescription (Prelude.Maybe [PlatformType])
documentDescription_platformTypes :: Lens' DocumentDescription (Maybe [PlatformType])
documentDescription_platformTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe [PlatformType]
platformTypes :: Maybe [PlatformType]
$sel:platformTypes:DocumentDescription' :: DocumentDescription -> Maybe [PlatformType]
platformTypes} -> Maybe [PlatformType]
platformTypes) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe [PlatformType]
a -> DocumentDescription
s {$sel:platformTypes:DocumentDescription' :: Maybe [PlatformType]
platformTypes = Maybe [PlatformType]
a} :: DocumentDescription) 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

-- | A list of SSM documents required by a document. For example, an
-- @ApplicationConfiguration@ document requires an
-- @ApplicationConfigurationSchema@ document.
documentDescription_requires :: Lens.Lens' DocumentDescription (Prelude.Maybe (Prelude.NonEmpty DocumentRequires))
documentDescription_requires :: Lens' DocumentDescription (Maybe (NonEmpty DocumentRequires))
documentDescription_requires = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe (NonEmpty DocumentRequires)
requires :: Maybe (NonEmpty DocumentRequires)
$sel:requires:DocumentDescription' :: DocumentDescription -> Maybe (NonEmpty DocumentRequires)
requires} -> Maybe (NonEmpty DocumentRequires)
requires) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe (NonEmpty DocumentRequires)
a -> DocumentDescription
s {$sel:requires:DocumentDescription' :: Maybe (NonEmpty DocumentRequires)
requires = Maybe (NonEmpty DocumentRequires)
a} :: DocumentDescription) 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

-- | Details about the review of a document.
documentDescription_reviewInformation :: Lens.Lens' DocumentDescription (Prelude.Maybe (Prelude.NonEmpty ReviewInformation))
documentDescription_reviewInformation :: Lens' DocumentDescription (Maybe (NonEmpty ReviewInformation))
documentDescription_reviewInformation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe (NonEmpty ReviewInformation)
reviewInformation :: Maybe (NonEmpty ReviewInformation)
$sel:reviewInformation:DocumentDescription' :: DocumentDescription -> Maybe (NonEmpty ReviewInformation)
reviewInformation} -> Maybe (NonEmpty ReviewInformation)
reviewInformation) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe (NonEmpty ReviewInformation)
a -> DocumentDescription
s {$sel:reviewInformation:DocumentDescription' :: Maybe (NonEmpty ReviewInformation)
reviewInformation = Maybe (NonEmpty ReviewInformation)
a} :: DocumentDescription) 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 current status of the review.
documentDescription_reviewStatus :: Lens.Lens' DocumentDescription (Prelude.Maybe ReviewStatus)
documentDescription_reviewStatus :: Lens' DocumentDescription (Maybe ReviewStatus)
documentDescription_reviewStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe ReviewStatus
reviewStatus :: Maybe ReviewStatus
$sel:reviewStatus:DocumentDescription' :: DocumentDescription -> Maybe ReviewStatus
reviewStatus} -> Maybe ReviewStatus
reviewStatus) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe ReviewStatus
a -> DocumentDescription
s {$sel:reviewStatus:DocumentDescription' :: Maybe ReviewStatus
reviewStatus = Maybe ReviewStatus
a} :: DocumentDescription)

-- | The schema version.
documentDescription_schemaVersion :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_schemaVersion :: Lens' DocumentDescription (Maybe Text)
documentDescription_schemaVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
schemaVersion :: Maybe Text
$sel:schemaVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
schemaVersion} -> Maybe Text
schemaVersion) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:schemaVersion:DocumentDescription' :: Maybe Text
schemaVersion = Maybe Text
a} :: DocumentDescription)

-- | The SHA1 hash of the document, which you can use for verification.
documentDescription_sha1 :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_sha1 :: Lens' DocumentDescription (Maybe Text)
documentDescription_sha1 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
sha1 :: Maybe Text
$sel:sha1:DocumentDescription' :: DocumentDescription -> Maybe Text
sha1} -> Maybe Text
sha1) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:sha1:DocumentDescription' :: Maybe Text
sha1 = Maybe Text
a} :: DocumentDescription)

-- | The status of the SSM document.
documentDescription_status :: Lens.Lens' DocumentDescription (Prelude.Maybe DocumentStatus)
documentDescription_status :: Lens' DocumentDescription (Maybe DocumentStatus)
documentDescription_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe DocumentStatus
status :: Maybe DocumentStatus
$sel:status:DocumentDescription' :: DocumentDescription -> Maybe DocumentStatus
status} -> Maybe DocumentStatus
status) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe DocumentStatus
a -> DocumentDescription
s {$sel:status:DocumentDescription' :: Maybe DocumentStatus
status = Maybe DocumentStatus
a} :: DocumentDescription)

-- | A message returned by Amazon Web Services Systems Manager that explains
-- the @Status@ value. For example, a @Failed@ status might be explained by
-- the @StatusInformation@ message, \"The specified S3 bucket doesn\'t
-- exist. Verify that the URL of the S3 bucket is correct.\"
documentDescription_statusInformation :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_statusInformation :: Lens' DocumentDescription (Maybe Text)
documentDescription_statusInformation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
statusInformation :: Maybe Text
$sel:statusInformation:DocumentDescription' :: DocumentDescription -> Maybe Text
statusInformation} -> Maybe Text
statusInformation) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:statusInformation:DocumentDescription' :: Maybe Text
statusInformation = Maybe Text
a} :: DocumentDescription)

-- | The tags, or metadata, that have been applied to the document.
documentDescription_tags :: Lens.Lens' DocumentDescription (Prelude.Maybe [Tag])
documentDescription_tags :: Lens' DocumentDescription (Maybe [Tag])
documentDescription_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:DocumentDescription' :: DocumentDescription -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe [Tag]
a -> DocumentDescription
s {$sel:tags:DocumentDescription' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: DocumentDescription) 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 target type which defines the kinds of resources the document can
-- run on. For example, @\/AWS::EC2::Instance@. For a list of valid
-- resource types, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-template-resource-type-ref.html Amazon Web Services resource and property types reference>
-- in the /CloudFormation User Guide/.
documentDescription_targetType :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_targetType :: Lens' DocumentDescription (Maybe Text)
documentDescription_targetType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
targetType :: Maybe Text
$sel:targetType:DocumentDescription' :: DocumentDescription -> Maybe Text
targetType} -> Maybe Text
targetType) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:targetType:DocumentDescription' :: Maybe Text
targetType = Maybe Text
a} :: DocumentDescription)

-- | The version of the artifact associated with the document.
documentDescription_versionName :: Lens.Lens' DocumentDescription (Prelude.Maybe Prelude.Text)
documentDescription_versionName :: Lens' DocumentDescription (Maybe Text)
documentDescription_versionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DocumentDescription' {Maybe Text
versionName :: Maybe Text
$sel:versionName:DocumentDescription' :: DocumentDescription -> Maybe Text
versionName} -> Maybe Text
versionName) (\s :: DocumentDescription
s@DocumentDescription' {} Maybe Text
a -> DocumentDescription
s {$sel:versionName:DocumentDescription' :: Maybe Text
versionName = Maybe Text
a} :: DocumentDescription)

instance Data.FromJSON DocumentDescription where
  parseJSON :: Value -> Parser DocumentDescription
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DocumentDescription"
      ( \Object
x ->
          Maybe Text
-> Maybe [AttachmentInformation]
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe DocumentFormat
-> Maybe DocumentType
-> Maybe Text
-> Maybe Text
-> Maybe DocumentHashType
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [DocumentParameter]
-> Maybe Text
-> Maybe [PlatformType]
-> Maybe (NonEmpty DocumentRequires)
-> Maybe (NonEmpty ReviewInformation)
-> Maybe ReviewStatus
-> Maybe Text
-> Maybe Text
-> Maybe DocumentStatus
-> Maybe Text
-> Maybe [Tag]
-> Maybe Text
-> Maybe Text
-> DocumentDescription
DocumentDescription'
            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
"ApprovedVersion")
            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
"AttachmentsInformation"
                            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
"Author")
            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
"Category" 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
"CategoryEnum" 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
"CreatedDate")
            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
"DefaultVersion")
            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
"Description")
            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
"DisplayName")
            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
"DocumentFormat")
            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
"DocumentType")
            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
"DocumentVersion")
            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
"Hash")
            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
"HashType")
            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
"LatestVersion")
            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
"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
"Parameters" 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
"PendingReviewVersion")
            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
"PlatformTypes" 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
"Requires")
            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
"ReviewInformation")
            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
"ReviewStatus")
            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
"SchemaVersion")
            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
"Sha1")
            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
"Status")
            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
"StatusInformation")
            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
"TargetType")
            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
"VersionName")
      )

instance Prelude.Hashable DocumentDescription where
  hashWithSalt :: Int -> DocumentDescription -> Int
hashWithSalt Int
_salt DocumentDescription' {Maybe [Text]
Maybe [AttachmentInformation]
Maybe [DocumentParameter]
Maybe [PlatformType]
Maybe [Tag]
Maybe (NonEmpty DocumentRequires)
Maybe (NonEmpty ReviewInformation)
Maybe Text
Maybe POSIX
Maybe DocumentFormat
Maybe DocumentHashType
Maybe DocumentStatus
Maybe DocumentType
Maybe ReviewStatus
versionName :: Maybe Text
targetType :: Maybe Text
tags :: Maybe [Tag]
statusInformation :: Maybe Text
status :: Maybe DocumentStatus
sha1 :: Maybe Text
schemaVersion :: Maybe Text
reviewStatus :: Maybe ReviewStatus
reviewInformation :: Maybe (NonEmpty ReviewInformation)
requires :: Maybe (NonEmpty DocumentRequires)
platformTypes :: Maybe [PlatformType]
pendingReviewVersion :: Maybe Text
parameters :: Maybe [DocumentParameter]
owner :: Maybe Text
name :: Maybe Text
latestVersion :: Maybe Text
hashType :: Maybe DocumentHashType
hash :: Maybe Text
documentVersion :: Maybe Text
documentType :: Maybe DocumentType
documentFormat :: Maybe DocumentFormat
displayName :: Maybe Text
description :: Maybe Text
defaultVersion :: Maybe Text
createdDate :: Maybe POSIX
categoryEnum :: Maybe [Text]
category :: Maybe [Text]
author :: Maybe Text
attachmentsInformation :: Maybe [AttachmentInformation]
approvedVersion :: Maybe Text
$sel:versionName:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:targetType:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:tags:DocumentDescription' :: DocumentDescription -> Maybe [Tag]
$sel:statusInformation:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:status:DocumentDescription' :: DocumentDescription -> Maybe DocumentStatus
$sel:sha1:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:schemaVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:reviewStatus:DocumentDescription' :: DocumentDescription -> Maybe ReviewStatus
$sel:reviewInformation:DocumentDescription' :: DocumentDescription -> Maybe (NonEmpty ReviewInformation)
$sel:requires:DocumentDescription' :: DocumentDescription -> Maybe (NonEmpty DocumentRequires)
$sel:platformTypes:DocumentDescription' :: DocumentDescription -> Maybe [PlatformType]
$sel:pendingReviewVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:parameters:DocumentDescription' :: DocumentDescription -> Maybe [DocumentParameter]
$sel:owner:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:name:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:latestVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:hashType:DocumentDescription' :: DocumentDescription -> Maybe DocumentHashType
$sel:hash:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:documentVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:documentType:DocumentDescription' :: DocumentDescription -> Maybe DocumentType
$sel:documentFormat:DocumentDescription' :: DocumentDescription -> Maybe DocumentFormat
$sel:displayName:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:description:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:defaultVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:createdDate:DocumentDescription' :: DocumentDescription -> Maybe POSIX
$sel:categoryEnum:DocumentDescription' :: DocumentDescription -> Maybe [Text]
$sel:category:DocumentDescription' :: DocumentDescription -> Maybe [Text]
$sel:author:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:attachmentsInformation:DocumentDescription' :: DocumentDescription -> Maybe [AttachmentInformation]
$sel:approvedVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
approvedVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AttachmentInformation]
attachmentsInformation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
author
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
category
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
categoryEnum
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
defaultVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
displayName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DocumentFormat
documentFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DocumentType
documentType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
documentVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
hash
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DocumentHashType
hashType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
latestVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
owner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DocumentParameter]
parameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pendingReviewVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PlatformType]
platformTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty DocumentRequires)
requires
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty ReviewInformation)
reviewInformation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReviewStatus
reviewStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
schemaVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sha1
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DocumentStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statusInformation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
targetType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
versionName

instance Prelude.NFData DocumentDescription where
  rnf :: DocumentDescription -> ()
rnf DocumentDescription' {Maybe [Text]
Maybe [AttachmentInformation]
Maybe [DocumentParameter]
Maybe [PlatformType]
Maybe [Tag]
Maybe (NonEmpty DocumentRequires)
Maybe (NonEmpty ReviewInformation)
Maybe Text
Maybe POSIX
Maybe DocumentFormat
Maybe DocumentHashType
Maybe DocumentStatus
Maybe DocumentType
Maybe ReviewStatus
versionName :: Maybe Text
targetType :: Maybe Text
tags :: Maybe [Tag]
statusInformation :: Maybe Text
status :: Maybe DocumentStatus
sha1 :: Maybe Text
schemaVersion :: Maybe Text
reviewStatus :: Maybe ReviewStatus
reviewInformation :: Maybe (NonEmpty ReviewInformation)
requires :: Maybe (NonEmpty DocumentRequires)
platformTypes :: Maybe [PlatformType]
pendingReviewVersion :: Maybe Text
parameters :: Maybe [DocumentParameter]
owner :: Maybe Text
name :: Maybe Text
latestVersion :: Maybe Text
hashType :: Maybe DocumentHashType
hash :: Maybe Text
documentVersion :: Maybe Text
documentType :: Maybe DocumentType
documentFormat :: Maybe DocumentFormat
displayName :: Maybe Text
description :: Maybe Text
defaultVersion :: Maybe Text
createdDate :: Maybe POSIX
categoryEnum :: Maybe [Text]
category :: Maybe [Text]
author :: Maybe Text
attachmentsInformation :: Maybe [AttachmentInformation]
approvedVersion :: Maybe Text
$sel:versionName:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:targetType:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:tags:DocumentDescription' :: DocumentDescription -> Maybe [Tag]
$sel:statusInformation:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:status:DocumentDescription' :: DocumentDescription -> Maybe DocumentStatus
$sel:sha1:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:schemaVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:reviewStatus:DocumentDescription' :: DocumentDescription -> Maybe ReviewStatus
$sel:reviewInformation:DocumentDescription' :: DocumentDescription -> Maybe (NonEmpty ReviewInformation)
$sel:requires:DocumentDescription' :: DocumentDescription -> Maybe (NonEmpty DocumentRequires)
$sel:platformTypes:DocumentDescription' :: DocumentDescription -> Maybe [PlatformType]
$sel:pendingReviewVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:parameters:DocumentDescription' :: DocumentDescription -> Maybe [DocumentParameter]
$sel:owner:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:name:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:latestVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:hashType:DocumentDescription' :: DocumentDescription -> Maybe DocumentHashType
$sel:hash:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:documentVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:documentType:DocumentDescription' :: DocumentDescription -> Maybe DocumentType
$sel:documentFormat:DocumentDescription' :: DocumentDescription -> Maybe DocumentFormat
$sel:displayName:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:description:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:defaultVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:createdDate:DocumentDescription' :: DocumentDescription -> Maybe POSIX
$sel:categoryEnum:DocumentDescription' :: DocumentDescription -> Maybe [Text]
$sel:category:DocumentDescription' :: DocumentDescription -> Maybe [Text]
$sel:author:DocumentDescription' :: DocumentDescription -> Maybe Text
$sel:attachmentsInformation:DocumentDescription' :: DocumentDescription -> Maybe [AttachmentInformation]
$sel:approvedVersion:DocumentDescription' :: DocumentDescription -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
approvedVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AttachmentInformation]
attachmentsInformation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
author
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
category
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
categoryEnum
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
displayName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DocumentFormat
documentFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DocumentType
documentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
documentVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
hash
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DocumentHashType
hashType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
latestVersion
      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
owner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DocumentParameter]
parameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pendingReviewVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PlatformType]
platformTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty DocumentRequires)
requires
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe (NonEmpty ReviewInformation)
reviewInformation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReviewStatus
reviewStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
schemaVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sha1
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DocumentStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
statusInformation
      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
targetType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
versionName