{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.DataExchange.UpdateRevision
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This operation updates a revision.
module Amazonka.DataExchange.UpdateRevision
  ( -- * Creating a Request
    UpdateRevision (..),
    newUpdateRevision,

    -- * Request Lenses
    updateRevision_comment,
    updateRevision_finalized,
    updateRevision_dataSetId,
    updateRevision_revisionId,

    -- * Destructuring the Response
    UpdateRevisionResponse (..),
    newUpdateRevisionResponse,

    -- * Response Lenses
    updateRevisionResponse_arn,
    updateRevisionResponse_comment,
    updateRevisionResponse_createdAt,
    updateRevisionResponse_dataSetId,
    updateRevisionResponse_finalized,
    updateRevisionResponse_id,
    updateRevisionResponse_revocationComment,
    updateRevisionResponse_revoked,
    updateRevisionResponse_revokedAt,
    updateRevisionResponse_sourceId,
    updateRevisionResponse_updatedAt,
    updateRevisionResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DataExchange.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateRevision' smart constructor.
data UpdateRevision = UpdateRevision'
  { -- | An optional comment about the revision.
    UpdateRevision -> Maybe Text
comment :: Prelude.Maybe Prelude.Text,
    -- | Finalizing a revision tells AWS Data Exchange that your changes to the
    -- assets in the revision are complete. After it\'s in this read-only
    -- state, you can publish the revision to your products.
    UpdateRevision -> Maybe Bool
finalized :: Prelude.Maybe Prelude.Bool,
    -- | The unique identifier for a data set.
    UpdateRevision -> Text
dataSetId :: Prelude.Text,
    -- | The unique identifier for a revision.
    UpdateRevision -> Text
revisionId :: Prelude.Text
  }
  deriving (UpdateRevision -> UpdateRevision -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRevision -> UpdateRevision -> Bool
$c/= :: UpdateRevision -> UpdateRevision -> Bool
== :: UpdateRevision -> UpdateRevision -> Bool
$c== :: UpdateRevision -> UpdateRevision -> Bool
Prelude.Eq, ReadPrec [UpdateRevision]
ReadPrec UpdateRevision
Int -> ReadS UpdateRevision
ReadS [UpdateRevision]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRevision]
$creadListPrec :: ReadPrec [UpdateRevision]
readPrec :: ReadPrec UpdateRevision
$creadPrec :: ReadPrec UpdateRevision
readList :: ReadS [UpdateRevision]
$creadList :: ReadS [UpdateRevision]
readsPrec :: Int -> ReadS UpdateRevision
$creadsPrec :: Int -> ReadS UpdateRevision
Prelude.Read, Int -> UpdateRevision -> ShowS
[UpdateRevision] -> ShowS
UpdateRevision -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRevision] -> ShowS
$cshowList :: [UpdateRevision] -> ShowS
show :: UpdateRevision -> String
$cshow :: UpdateRevision -> String
showsPrec :: Int -> UpdateRevision -> ShowS
$cshowsPrec :: Int -> UpdateRevision -> ShowS
Prelude.Show, forall x. Rep UpdateRevision x -> UpdateRevision
forall x. UpdateRevision -> Rep UpdateRevision x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRevision x -> UpdateRevision
$cfrom :: forall x. UpdateRevision -> Rep UpdateRevision x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRevision' 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:
--
-- 'comment', 'updateRevision_comment' - An optional comment about the revision.
--
-- 'finalized', 'updateRevision_finalized' - Finalizing a revision tells AWS Data Exchange that your changes to the
-- assets in the revision are complete. After it\'s in this read-only
-- state, you can publish the revision to your products.
--
-- 'dataSetId', 'updateRevision_dataSetId' - The unique identifier for a data set.
--
-- 'revisionId', 'updateRevision_revisionId' - The unique identifier for a revision.
newUpdateRevision ::
  -- | 'dataSetId'
  Prelude.Text ->
  -- | 'revisionId'
  Prelude.Text ->
  UpdateRevision
newUpdateRevision :: Text -> Text -> UpdateRevision
newUpdateRevision Text
pDataSetId_ Text
pRevisionId_ =
  UpdateRevision'
    { $sel:comment:UpdateRevision' :: Maybe Text
comment = forall a. Maybe a
Prelude.Nothing,
      $sel:finalized:UpdateRevision' :: Maybe Bool
finalized = forall a. Maybe a
Prelude.Nothing,
      $sel:dataSetId:UpdateRevision' :: Text
dataSetId = Text
pDataSetId_,
      $sel:revisionId:UpdateRevision' :: Text
revisionId = Text
pRevisionId_
    }

-- | An optional comment about the revision.
updateRevision_comment :: Lens.Lens' UpdateRevision (Prelude.Maybe Prelude.Text)
updateRevision_comment :: Lens' UpdateRevision (Maybe Text)
updateRevision_comment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevision' {Maybe Text
comment :: Maybe Text
$sel:comment:UpdateRevision' :: UpdateRevision -> Maybe Text
comment} -> Maybe Text
comment) (\s :: UpdateRevision
s@UpdateRevision' {} Maybe Text
a -> UpdateRevision
s {$sel:comment:UpdateRevision' :: Maybe Text
comment = Maybe Text
a} :: UpdateRevision)

-- | Finalizing a revision tells AWS Data Exchange that your changes to the
-- assets in the revision are complete. After it\'s in this read-only
-- state, you can publish the revision to your products.
updateRevision_finalized :: Lens.Lens' UpdateRevision (Prelude.Maybe Prelude.Bool)
updateRevision_finalized :: Lens' UpdateRevision (Maybe Bool)
updateRevision_finalized = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevision' {Maybe Bool
finalized :: Maybe Bool
$sel:finalized:UpdateRevision' :: UpdateRevision -> Maybe Bool
finalized} -> Maybe Bool
finalized) (\s :: UpdateRevision
s@UpdateRevision' {} Maybe Bool
a -> UpdateRevision
s {$sel:finalized:UpdateRevision' :: Maybe Bool
finalized = Maybe Bool
a} :: UpdateRevision)

-- | The unique identifier for a data set.
updateRevision_dataSetId :: Lens.Lens' UpdateRevision Prelude.Text
updateRevision_dataSetId :: Lens' UpdateRevision Text
updateRevision_dataSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevision' {Text
dataSetId :: Text
$sel:dataSetId:UpdateRevision' :: UpdateRevision -> Text
dataSetId} -> Text
dataSetId) (\s :: UpdateRevision
s@UpdateRevision' {} Text
a -> UpdateRevision
s {$sel:dataSetId:UpdateRevision' :: Text
dataSetId = Text
a} :: UpdateRevision)

-- | The unique identifier for a revision.
updateRevision_revisionId :: Lens.Lens' UpdateRevision Prelude.Text
updateRevision_revisionId :: Lens' UpdateRevision Text
updateRevision_revisionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevision' {Text
revisionId :: Text
$sel:revisionId:UpdateRevision' :: UpdateRevision -> Text
revisionId} -> Text
revisionId) (\s :: UpdateRevision
s@UpdateRevision' {} Text
a -> UpdateRevision
s {$sel:revisionId:UpdateRevision' :: Text
revisionId = Text
a} :: UpdateRevision)

instance Core.AWSRequest UpdateRevision where
  type
    AWSResponse UpdateRevision =
      UpdateRevisionResponse
  request :: (Service -> Service) -> UpdateRevision -> Request UpdateRevision
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateRevision
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateRevision)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe ISO8601
-> Maybe Text
-> Maybe ISO8601
-> Int
-> UpdateRevisionResponse
UpdateRevisionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"Comment")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreatedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DataSetId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Finalized")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RevocationComment")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Revoked")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RevokedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SourceId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"UpdatedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable UpdateRevision where
  hashWithSalt :: Int -> UpdateRevision -> Int
hashWithSalt Int
_salt UpdateRevision' {Maybe Bool
Maybe Text
Text
revisionId :: Text
dataSetId :: Text
finalized :: Maybe Bool
comment :: Maybe Text
$sel:revisionId:UpdateRevision' :: UpdateRevision -> Text
$sel:dataSetId:UpdateRevision' :: UpdateRevision -> Text
$sel:finalized:UpdateRevision' :: UpdateRevision -> Maybe Bool
$sel:comment:UpdateRevision' :: UpdateRevision -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
comment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
finalized
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dataSetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
revisionId

instance Prelude.NFData UpdateRevision where
  rnf :: UpdateRevision -> ()
rnf UpdateRevision' {Maybe Bool
Maybe Text
Text
revisionId :: Text
dataSetId :: Text
finalized :: Maybe Bool
comment :: Maybe Text
$sel:revisionId:UpdateRevision' :: UpdateRevision -> Text
$sel:dataSetId:UpdateRevision' :: UpdateRevision -> Text
$sel:finalized:UpdateRevision' :: UpdateRevision -> Maybe Bool
$sel:comment:UpdateRevision' :: UpdateRevision -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
comment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
finalized
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dataSetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
revisionId

instance Data.ToHeaders UpdateRevision where
  toHeaders :: UpdateRevision -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateRevision where
  toJSON :: UpdateRevision -> Value
toJSON UpdateRevision' {Maybe Bool
Maybe Text
Text
revisionId :: Text
dataSetId :: Text
finalized :: Maybe Bool
comment :: Maybe Text
$sel:revisionId:UpdateRevision' :: UpdateRevision -> Text
$sel:dataSetId:UpdateRevision' :: UpdateRevision -> Text
$sel:finalized:UpdateRevision' :: UpdateRevision -> Maybe Bool
$sel:comment:UpdateRevision' :: UpdateRevision -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Comment" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
comment,
            (Key
"Finalized" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
finalized
          ]
      )

instance Data.ToPath UpdateRevision where
  toPath :: UpdateRevision -> ByteString
toPath UpdateRevision' {Maybe Bool
Maybe Text
Text
revisionId :: Text
dataSetId :: Text
finalized :: Maybe Bool
comment :: Maybe Text
$sel:revisionId:UpdateRevision' :: UpdateRevision -> Text
$sel:dataSetId:UpdateRevision' :: UpdateRevision -> Text
$sel:finalized:UpdateRevision' :: UpdateRevision -> Maybe Bool
$sel:comment:UpdateRevision' :: UpdateRevision -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/data-sets/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
dataSetId,
        ByteString
"/revisions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
revisionId
      ]

instance Data.ToQuery UpdateRevision where
  toQuery :: UpdateRevision -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateRevisionResponse' smart constructor.
data UpdateRevisionResponse = UpdateRevisionResponse'
  { -- | The ARN for the revision.
    UpdateRevisionResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | An optional comment about the revision.
    UpdateRevisionResponse -> Maybe Text
comment :: Prelude.Maybe Prelude.Text,
    -- | The date and time that the revision was created, in ISO 8601 format.
    UpdateRevisionResponse -> Maybe ISO8601
createdAt :: Prelude.Maybe Data.ISO8601,
    -- | The unique identifier for the data set associated with the data set
    -- revision.
    UpdateRevisionResponse -> Maybe Text
dataSetId :: Prelude.Maybe Prelude.Text,
    -- | To publish a revision to a data set in a product, the revision must
    -- first be finalized. Finalizing a revision tells AWS Data Exchange that
    -- changes to the assets in the revision are complete. After it\'s in this
    -- read-only state, you can publish the revision to your products.
    -- Finalized revisions can be published through the AWS Data Exchange
    -- console or the AWS Marketplace Catalog API, using the StartChangeSet AWS
    -- Marketplace Catalog API action. When using the API, revisions are
    -- uniquely identified by their ARN.
    UpdateRevisionResponse -> Maybe Bool
finalized :: Prelude.Maybe Prelude.Bool,
    -- | The unique identifier for the revision.
    UpdateRevisionResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | A required comment to inform subscribers of the reason their access to
    -- the revision was revoked.
    UpdateRevisionResponse -> Maybe Text
revocationComment :: Prelude.Maybe Prelude.Text,
    -- | A status indicating that subscribers\' access to the revision was
    -- revoked.
    UpdateRevisionResponse -> Maybe Bool
revoked :: Prelude.Maybe Prelude.Bool,
    -- | The date and time that the revision was revoked, in ISO 8601 format.
    UpdateRevisionResponse -> Maybe ISO8601
revokedAt :: Prelude.Maybe Data.ISO8601,
    -- | The revision ID of the owned revision corresponding to the entitled
    -- revision being viewed. This parameter is returned when a revision owner
    -- is viewing the entitled copy of its owned revision.
    UpdateRevisionResponse -> Maybe Text
sourceId :: Prelude.Maybe Prelude.Text,
    -- | The date and time that the revision was last updated, in ISO 8601
    -- format.
    UpdateRevisionResponse -> Maybe ISO8601
updatedAt :: Prelude.Maybe Data.ISO8601,
    -- | The response's http status code.
    UpdateRevisionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateRevisionResponse -> UpdateRevisionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRevisionResponse -> UpdateRevisionResponse -> Bool
$c/= :: UpdateRevisionResponse -> UpdateRevisionResponse -> Bool
== :: UpdateRevisionResponse -> UpdateRevisionResponse -> Bool
$c== :: UpdateRevisionResponse -> UpdateRevisionResponse -> Bool
Prelude.Eq, ReadPrec [UpdateRevisionResponse]
ReadPrec UpdateRevisionResponse
Int -> ReadS UpdateRevisionResponse
ReadS [UpdateRevisionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRevisionResponse]
$creadListPrec :: ReadPrec [UpdateRevisionResponse]
readPrec :: ReadPrec UpdateRevisionResponse
$creadPrec :: ReadPrec UpdateRevisionResponse
readList :: ReadS [UpdateRevisionResponse]
$creadList :: ReadS [UpdateRevisionResponse]
readsPrec :: Int -> ReadS UpdateRevisionResponse
$creadsPrec :: Int -> ReadS UpdateRevisionResponse
Prelude.Read, Int -> UpdateRevisionResponse -> ShowS
[UpdateRevisionResponse] -> ShowS
UpdateRevisionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRevisionResponse] -> ShowS
$cshowList :: [UpdateRevisionResponse] -> ShowS
show :: UpdateRevisionResponse -> String
$cshow :: UpdateRevisionResponse -> String
showsPrec :: Int -> UpdateRevisionResponse -> ShowS
$cshowsPrec :: Int -> UpdateRevisionResponse -> ShowS
Prelude.Show, forall x. Rep UpdateRevisionResponse x -> UpdateRevisionResponse
forall x. UpdateRevisionResponse -> Rep UpdateRevisionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRevisionResponse x -> UpdateRevisionResponse
$cfrom :: forall x. UpdateRevisionResponse -> Rep UpdateRevisionResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRevisionResponse' 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', 'updateRevisionResponse_arn' - The ARN for the revision.
--
-- 'comment', 'updateRevisionResponse_comment' - An optional comment about the revision.
--
-- 'createdAt', 'updateRevisionResponse_createdAt' - The date and time that the revision was created, in ISO 8601 format.
--
-- 'dataSetId', 'updateRevisionResponse_dataSetId' - The unique identifier for the data set associated with the data set
-- revision.
--
-- 'finalized', 'updateRevisionResponse_finalized' - To publish a revision to a data set in a product, the revision must
-- first be finalized. Finalizing a revision tells AWS Data Exchange that
-- changes to the assets in the revision are complete. After it\'s in this
-- read-only state, you can publish the revision to your products.
-- Finalized revisions can be published through the AWS Data Exchange
-- console or the AWS Marketplace Catalog API, using the StartChangeSet AWS
-- Marketplace Catalog API action. When using the API, revisions are
-- uniquely identified by their ARN.
--
-- 'id', 'updateRevisionResponse_id' - The unique identifier for the revision.
--
-- 'revocationComment', 'updateRevisionResponse_revocationComment' - A required comment to inform subscribers of the reason their access to
-- the revision was revoked.
--
-- 'revoked', 'updateRevisionResponse_revoked' - A status indicating that subscribers\' access to the revision was
-- revoked.
--
-- 'revokedAt', 'updateRevisionResponse_revokedAt' - The date and time that the revision was revoked, in ISO 8601 format.
--
-- 'sourceId', 'updateRevisionResponse_sourceId' - The revision ID of the owned revision corresponding to the entitled
-- revision being viewed. This parameter is returned when a revision owner
-- is viewing the entitled copy of its owned revision.
--
-- 'updatedAt', 'updateRevisionResponse_updatedAt' - The date and time that the revision was last updated, in ISO 8601
-- format.
--
-- 'httpStatus', 'updateRevisionResponse_httpStatus' - The response's http status code.
newUpdateRevisionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateRevisionResponse
newUpdateRevisionResponse :: Int -> UpdateRevisionResponse
newUpdateRevisionResponse Int
pHttpStatus_ =
  UpdateRevisionResponse'
    { $sel:arn:UpdateRevisionResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:comment:UpdateRevisionResponse' :: Maybe Text
comment = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:UpdateRevisionResponse' :: Maybe ISO8601
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:dataSetId:UpdateRevisionResponse' :: Maybe Text
dataSetId = forall a. Maybe a
Prelude.Nothing,
      $sel:finalized:UpdateRevisionResponse' :: Maybe Bool
finalized = forall a. Maybe a
Prelude.Nothing,
      $sel:id:UpdateRevisionResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:revocationComment:UpdateRevisionResponse' :: Maybe Text
revocationComment = forall a. Maybe a
Prelude.Nothing,
      $sel:revoked:UpdateRevisionResponse' :: Maybe Bool
revoked = forall a. Maybe a
Prelude.Nothing,
      $sel:revokedAt:UpdateRevisionResponse' :: Maybe ISO8601
revokedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceId:UpdateRevisionResponse' :: Maybe Text
sourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedAt:UpdateRevisionResponse' :: Maybe ISO8601
updatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateRevisionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN for the revision.
updateRevisionResponse_arn :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.Text)
updateRevisionResponse_arn :: Lens' UpdateRevisionResponse (Maybe Text)
updateRevisionResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe Text
a -> UpdateRevisionResponse
s {$sel:arn:UpdateRevisionResponse' :: Maybe Text
arn = Maybe Text
a} :: UpdateRevisionResponse)

-- | An optional comment about the revision.
updateRevisionResponse_comment :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.Text)
updateRevisionResponse_comment :: Lens' UpdateRevisionResponse (Maybe Text)
updateRevisionResponse_comment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe Text
comment :: Maybe Text
$sel:comment:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
comment} -> Maybe Text
comment) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe Text
a -> UpdateRevisionResponse
s {$sel:comment:UpdateRevisionResponse' :: Maybe Text
comment = Maybe Text
a} :: UpdateRevisionResponse)

-- | The date and time that the revision was created, in ISO 8601 format.
updateRevisionResponse_createdAt :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.UTCTime)
updateRevisionResponse_createdAt :: Lens' UpdateRevisionResponse (Maybe UTCTime)
updateRevisionResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe ISO8601
createdAt :: Maybe ISO8601
$sel:createdAt:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe ISO8601
createdAt} -> Maybe ISO8601
createdAt) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe ISO8601
a -> UpdateRevisionResponse
s {$sel:createdAt:UpdateRevisionResponse' :: Maybe ISO8601
createdAt = Maybe ISO8601
a} :: UpdateRevisionResponse) 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 unique identifier for the data set associated with the data set
-- revision.
updateRevisionResponse_dataSetId :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.Text)
updateRevisionResponse_dataSetId :: Lens' UpdateRevisionResponse (Maybe Text)
updateRevisionResponse_dataSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe Text
dataSetId :: Maybe Text
$sel:dataSetId:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
dataSetId} -> Maybe Text
dataSetId) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe Text
a -> UpdateRevisionResponse
s {$sel:dataSetId:UpdateRevisionResponse' :: Maybe Text
dataSetId = Maybe Text
a} :: UpdateRevisionResponse)

-- | To publish a revision to a data set in a product, the revision must
-- first be finalized. Finalizing a revision tells AWS Data Exchange that
-- changes to the assets in the revision are complete. After it\'s in this
-- read-only state, you can publish the revision to your products.
-- Finalized revisions can be published through the AWS Data Exchange
-- console or the AWS Marketplace Catalog API, using the StartChangeSet AWS
-- Marketplace Catalog API action. When using the API, revisions are
-- uniquely identified by their ARN.
updateRevisionResponse_finalized :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.Bool)
updateRevisionResponse_finalized :: Lens' UpdateRevisionResponse (Maybe Bool)
updateRevisionResponse_finalized = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe Bool
finalized :: Maybe Bool
$sel:finalized:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Bool
finalized} -> Maybe Bool
finalized) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe Bool
a -> UpdateRevisionResponse
s {$sel:finalized:UpdateRevisionResponse' :: Maybe Bool
finalized = Maybe Bool
a} :: UpdateRevisionResponse)

-- | The unique identifier for the revision.
updateRevisionResponse_id :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.Text)
updateRevisionResponse_id :: Lens' UpdateRevisionResponse (Maybe Text)
updateRevisionResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe Text
id :: Maybe Text
$sel:id:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe Text
a -> UpdateRevisionResponse
s {$sel:id:UpdateRevisionResponse' :: Maybe Text
id = Maybe Text
a} :: UpdateRevisionResponse)

-- | A required comment to inform subscribers of the reason their access to
-- the revision was revoked.
updateRevisionResponse_revocationComment :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.Text)
updateRevisionResponse_revocationComment :: Lens' UpdateRevisionResponse (Maybe Text)
updateRevisionResponse_revocationComment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe Text
revocationComment :: Maybe Text
$sel:revocationComment:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
revocationComment} -> Maybe Text
revocationComment) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe Text
a -> UpdateRevisionResponse
s {$sel:revocationComment:UpdateRevisionResponse' :: Maybe Text
revocationComment = Maybe Text
a} :: UpdateRevisionResponse)

-- | A status indicating that subscribers\' access to the revision was
-- revoked.
updateRevisionResponse_revoked :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.Bool)
updateRevisionResponse_revoked :: Lens' UpdateRevisionResponse (Maybe Bool)
updateRevisionResponse_revoked = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe Bool
revoked :: Maybe Bool
$sel:revoked:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Bool
revoked} -> Maybe Bool
revoked) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe Bool
a -> UpdateRevisionResponse
s {$sel:revoked:UpdateRevisionResponse' :: Maybe Bool
revoked = Maybe Bool
a} :: UpdateRevisionResponse)

-- | The date and time that the revision was revoked, in ISO 8601 format.
updateRevisionResponse_revokedAt :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.UTCTime)
updateRevisionResponse_revokedAt :: Lens' UpdateRevisionResponse (Maybe UTCTime)
updateRevisionResponse_revokedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe ISO8601
revokedAt :: Maybe ISO8601
$sel:revokedAt:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe ISO8601
revokedAt} -> Maybe ISO8601
revokedAt) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe ISO8601
a -> UpdateRevisionResponse
s {$sel:revokedAt:UpdateRevisionResponse' :: Maybe ISO8601
revokedAt = Maybe ISO8601
a} :: UpdateRevisionResponse) 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 revision ID of the owned revision corresponding to the entitled
-- revision being viewed. This parameter is returned when a revision owner
-- is viewing the entitled copy of its owned revision.
updateRevisionResponse_sourceId :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.Text)
updateRevisionResponse_sourceId :: Lens' UpdateRevisionResponse (Maybe Text)
updateRevisionResponse_sourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe Text
sourceId :: Maybe Text
$sel:sourceId:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
sourceId} -> Maybe Text
sourceId) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe Text
a -> UpdateRevisionResponse
s {$sel:sourceId:UpdateRevisionResponse' :: Maybe Text
sourceId = Maybe Text
a} :: UpdateRevisionResponse)

-- | The date and time that the revision was last updated, in ISO 8601
-- format.
updateRevisionResponse_updatedAt :: Lens.Lens' UpdateRevisionResponse (Prelude.Maybe Prelude.UTCTime)
updateRevisionResponse_updatedAt :: Lens' UpdateRevisionResponse (Maybe UTCTime)
updateRevisionResponse_updatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Maybe ISO8601
updatedAt :: Maybe ISO8601
$sel:updatedAt:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe ISO8601
updatedAt} -> Maybe ISO8601
updatedAt) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Maybe ISO8601
a -> UpdateRevisionResponse
s {$sel:updatedAt:UpdateRevisionResponse' :: Maybe ISO8601
updatedAt = Maybe ISO8601
a} :: UpdateRevisionResponse) 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 response's http status code.
updateRevisionResponse_httpStatus :: Lens.Lens' UpdateRevisionResponse Prelude.Int
updateRevisionResponse_httpStatus :: Lens' UpdateRevisionResponse Int
updateRevisionResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRevisionResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateRevisionResponse' :: UpdateRevisionResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateRevisionResponse
s@UpdateRevisionResponse' {} Int
a -> UpdateRevisionResponse
s {$sel:httpStatus:UpdateRevisionResponse' :: Int
httpStatus = Int
a} :: UpdateRevisionResponse)

instance Prelude.NFData UpdateRevisionResponse where
  rnf :: UpdateRevisionResponse -> ()
rnf UpdateRevisionResponse' {Int
Maybe Bool
Maybe Text
Maybe ISO8601
httpStatus :: Int
updatedAt :: Maybe ISO8601
sourceId :: Maybe Text
revokedAt :: Maybe ISO8601
revoked :: Maybe Bool
revocationComment :: Maybe Text
id :: Maybe Text
finalized :: Maybe Bool
dataSetId :: Maybe Text
createdAt :: Maybe ISO8601
comment :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:UpdateRevisionResponse' :: UpdateRevisionResponse -> Int
$sel:updatedAt:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe ISO8601
$sel:sourceId:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
$sel:revokedAt:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe ISO8601
$sel:revoked:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Bool
$sel:revocationComment:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
$sel:id:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
$sel:finalized:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Bool
$sel:dataSetId:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
$sel:createdAt:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe ISO8601
$sel:comment:UpdateRevisionResponse' :: UpdateRevisionResponse -> Maybe Text
$sel:arn:UpdateRevisionResponse' :: UpdateRevisionResponse -> 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 Text
comment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dataSetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
finalized
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
revocationComment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
revoked
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
revokedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
updatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus