{-# 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.GetRevision
-- 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 returns information about a revision.
module Amazonka.DataExchange.GetRevision
  ( -- * Creating a Request
    GetRevision (..),
    newGetRevision,

    -- * Request Lenses
    getRevision_dataSetId,
    getRevision_revisionId,

    -- * Destructuring the Response
    GetRevisionResponse (..),
    newGetRevisionResponse,

    -- * Response Lenses
    getRevisionResponse_arn,
    getRevisionResponse_comment,
    getRevisionResponse_createdAt,
    getRevisionResponse_dataSetId,
    getRevisionResponse_finalized,
    getRevisionResponse_id,
    getRevisionResponse_revocationComment,
    getRevisionResponse_revoked,
    getRevisionResponse_revokedAt,
    getRevisionResponse_sourceId,
    getRevisionResponse_tags,
    getRevisionResponse_updatedAt,
    getRevisionResponse_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:/ 'newGetRevision' smart constructor.
data GetRevision = GetRevision'
  { -- | The unique identifier for a data set.
    GetRevision -> Text
dataSetId :: Prelude.Text,
    -- | The unique identifier for a revision.
    GetRevision -> Text
revisionId :: Prelude.Text
  }
  deriving (GetRevision -> GetRevision -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRevision -> GetRevision -> Bool
$c/= :: GetRevision -> GetRevision -> Bool
== :: GetRevision -> GetRevision -> Bool
$c== :: GetRevision -> GetRevision -> Bool
Prelude.Eq, ReadPrec [GetRevision]
ReadPrec GetRevision
Int -> ReadS GetRevision
ReadS [GetRevision]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRevision]
$creadListPrec :: ReadPrec [GetRevision]
readPrec :: ReadPrec GetRevision
$creadPrec :: ReadPrec GetRevision
readList :: ReadS [GetRevision]
$creadList :: ReadS [GetRevision]
readsPrec :: Int -> ReadS GetRevision
$creadsPrec :: Int -> ReadS GetRevision
Prelude.Read, Int -> GetRevision -> ShowS
[GetRevision] -> ShowS
GetRevision -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRevision] -> ShowS
$cshowList :: [GetRevision] -> ShowS
show :: GetRevision -> String
$cshow :: GetRevision -> String
showsPrec :: Int -> GetRevision -> ShowS
$cshowsPrec :: Int -> GetRevision -> ShowS
Prelude.Show, forall x. Rep GetRevision x -> GetRevision
forall x. GetRevision -> Rep GetRevision x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRevision x -> GetRevision
$cfrom :: forall x. GetRevision -> Rep GetRevision x
Prelude.Generic)

-- |
-- Create a value of 'GetRevision' 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:
--
-- 'dataSetId', 'getRevision_dataSetId' - The unique identifier for a data set.
--
-- 'revisionId', 'getRevision_revisionId' - The unique identifier for a revision.
newGetRevision ::
  -- | 'dataSetId'
  Prelude.Text ->
  -- | 'revisionId'
  Prelude.Text ->
  GetRevision
newGetRevision :: Text -> Text -> GetRevision
newGetRevision Text
pDataSetId_ Text
pRevisionId_ =
  GetRevision'
    { $sel:dataSetId:GetRevision' :: Text
dataSetId = Text
pDataSetId_,
      $sel:revisionId:GetRevision' :: Text
revisionId = Text
pRevisionId_
    }

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

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

instance Core.AWSRequest GetRevision where
  type AWSResponse GetRevision = GetRevisionResponse
  request :: (Service -> Service) -> GetRevision -> Request GetRevision
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetRevision
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetRevision)))
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 (HashMap Text Text)
-> Maybe ISO8601
-> Int
-> GetRevisionResponse
GetRevisionResponse'
            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
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> 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 GetRevision where
  hashWithSalt :: Int -> GetRevision -> Int
hashWithSalt Int
_salt GetRevision' {Text
revisionId :: Text
dataSetId :: Text
$sel:revisionId:GetRevision' :: GetRevision -> Text
$sel:dataSetId:GetRevision' :: GetRevision -> Text
..} =
    Int
_salt
      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 GetRevision where
  rnf :: GetRevision -> ()
rnf GetRevision' {Text
revisionId :: Text
dataSetId :: Text
$sel:revisionId:GetRevision' :: GetRevision -> Text
$sel:dataSetId:GetRevision' :: GetRevision -> Text
..} =
    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 GetRevision where
  toHeaders :: GetRevision -> 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.ToPath GetRevision where
  toPath :: GetRevision -> ByteString
toPath GetRevision' {Text
revisionId :: Text
dataSetId :: Text
$sel:revisionId:GetRevision' :: GetRevision -> Text
$sel:dataSetId:GetRevision' :: GetRevision -> 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 GetRevision where
  toQuery :: GetRevision -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newGetRevisionResponse' smart constructor.
data GetRevisionResponse = GetRevisionResponse'
  { -- | The ARN for the revision.
    GetRevisionResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | An optional comment about the revision.
    GetRevisionResponse -> Maybe Text
comment :: Prelude.Maybe Prelude.Text,
    -- | The date and time that the revision was created, in ISO 8601 format.
    GetRevisionResponse -> Maybe ISO8601
createdAt :: Prelude.Maybe Data.ISO8601,
    -- | The unique identifier for the data set associated with the data set
    -- revision.
    GetRevisionResponse -> 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
    -- 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.
    -- 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.
    GetRevisionResponse -> Maybe Bool
finalized :: Prelude.Maybe Prelude.Bool,
    -- | The unique identifier for the revision.
    GetRevisionResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | A required comment to inform subscribers of the reason their access to
    -- the revision was revoked.
    GetRevisionResponse -> Maybe Text
revocationComment :: Prelude.Maybe Prelude.Text,
    -- | A status indicating that subscribers\' access to the revision was
    -- revoked.
    GetRevisionResponse -> Maybe Bool
revoked :: Prelude.Maybe Prelude.Bool,
    -- | The date and time that the revision was revoked, in ISO 8601 format.
    GetRevisionResponse -> 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.
    GetRevisionResponse -> Maybe Text
sourceId :: Prelude.Maybe Prelude.Text,
    -- | The tags for the revision.
    GetRevisionResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The date and time that the revision was last updated, in ISO 8601
    -- format.
    GetRevisionResponse -> Maybe ISO8601
updatedAt :: Prelude.Maybe Data.ISO8601,
    -- | The response's http status code.
    GetRevisionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetRevisionResponse -> GetRevisionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRevisionResponse -> GetRevisionResponse -> Bool
$c/= :: GetRevisionResponse -> GetRevisionResponse -> Bool
== :: GetRevisionResponse -> GetRevisionResponse -> Bool
$c== :: GetRevisionResponse -> GetRevisionResponse -> Bool
Prelude.Eq, ReadPrec [GetRevisionResponse]
ReadPrec GetRevisionResponse
Int -> ReadS GetRevisionResponse
ReadS [GetRevisionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRevisionResponse]
$creadListPrec :: ReadPrec [GetRevisionResponse]
readPrec :: ReadPrec GetRevisionResponse
$creadPrec :: ReadPrec GetRevisionResponse
readList :: ReadS [GetRevisionResponse]
$creadList :: ReadS [GetRevisionResponse]
readsPrec :: Int -> ReadS GetRevisionResponse
$creadsPrec :: Int -> ReadS GetRevisionResponse
Prelude.Read, Int -> GetRevisionResponse -> ShowS
[GetRevisionResponse] -> ShowS
GetRevisionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRevisionResponse] -> ShowS
$cshowList :: [GetRevisionResponse] -> ShowS
show :: GetRevisionResponse -> String
$cshow :: GetRevisionResponse -> String
showsPrec :: Int -> GetRevisionResponse -> ShowS
$cshowsPrec :: Int -> GetRevisionResponse -> ShowS
Prelude.Show, forall x. Rep GetRevisionResponse x -> GetRevisionResponse
forall x. GetRevisionResponse -> Rep GetRevisionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRevisionResponse x -> GetRevisionResponse
$cfrom :: forall x. GetRevisionResponse -> Rep GetRevisionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetRevisionResponse' 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', 'getRevisionResponse_arn' - The ARN for the revision.
--
-- 'comment', 'getRevisionResponse_comment' - An optional comment about the revision.
--
-- 'createdAt', 'getRevisionResponse_createdAt' - The date and time that the revision was created, in ISO 8601 format.
--
-- 'dataSetId', 'getRevisionResponse_dataSetId' - The unique identifier for the data set associated with the data set
-- revision.
--
-- 'finalized', 'getRevisionResponse_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
-- 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.
-- 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', 'getRevisionResponse_id' - The unique identifier for the revision.
--
-- 'revocationComment', 'getRevisionResponse_revocationComment' - A required comment to inform subscribers of the reason their access to
-- the revision was revoked.
--
-- 'revoked', 'getRevisionResponse_revoked' - A status indicating that subscribers\' access to the revision was
-- revoked.
--
-- 'revokedAt', 'getRevisionResponse_revokedAt' - The date and time that the revision was revoked, in ISO 8601 format.
--
-- 'sourceId', 'getRevisionResponse_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.
--
-- 'tags', 'getRevisionResponse_tags' - The tags for the revision.
--
-- 'updatedAt', 'getRevisionResponse_updatedAt' - The date and time that the revision was last updated, in ISO 8601
-- format.
--
-- 'httpStatus', 'getRevisionResponse_httpStatus' - The response's http status code.
newGetRevisionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetRevisionResponse
newGetRevisionResponse :: Int -> GetRevisionResponse
newGetRevisionResponse Int
pHttpStatus_ =
  GetRevisionResponse'
    { $sel:arn:GetRevisionResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:comment:GetRevisionResponse' :: Maybe Text
comment = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:GetRevisionResponse' :: Maybe ISO8601
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:dataSetId:GetRevisionResponse' :: Maybe Text
dataSetId = forall a. Maybe a
Prelude.Nothing,
      $sel:finalized:GetRevisionResponse' :: Maybe Bool
finalized = forall a. Maybe a
Prelude.Nothing,
      $sel:id:GetRevisionResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:revocationComment:GetRevisionResponse' :: Maybe Text
revocationComment = forall a. Maybe a
Prelude.Nothing,
      $sel:revoked:GetRevisionResponse' :: Maybe Bool
revoked = forall a. Maybe a
Prelude.Nothing,
      $sel:revokedAt:GetRevisionResponse' :: Maybe ISO8601
revokedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceId:GetRevisionResponse' :: Maybe Text
sourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetRevisionResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedAt:GetRevisionResponse' :: Maybe ISO8601
updatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetRevisionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

-- | The date and time that the revision was created, in ISO 8601 format.
getRevisionResponse_createdAt :: Lens.Lens' GetRevisionResponse (Prelude.Maybe Prelude.UTCTime)
getRevisionResponse_createdAt :: Lens' GetRevisionResponse (Maybe UTCTime)
getRevisionResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRevisionResponse' {Maybe ISO8601
createdAt :: Maybe ISO8601
$sel:createdAt:GetRevisionResponse' :: GetRevisionResponse -> Maybe ISO8601
createdAt} -> Maybe ISO8601
createdAt) (\s :: GetRevisionResponse
s@GetRevisionResponse' {} Maybe ISO8601
a -> GetRevisionResponse
s {$sel:createdAt:GetRevisionResponse' :: Maybe ISO8601
createdAt = Maybe ISO8601
a} :: GetRevisionResponse) 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.
getRevisionResponse_dataSetId :: Lens.Lens' GetRevisionResponse (Prelude.Maybe Prelude.Text)
getRevisionResponse_dataSetId :: Lens' GetRevisionResponse (Maybe Text)
getRevisionResponse_dataSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRevisionResponse' {Maybe Text
dataSetId :: Maybe Text
$sel:dataSetId:GetRevisionResponse' :: GetRevisionResponse -> Maybe Text
dataSetId} -> Maybe Text
dataSetId) (\s :: GetRevisionResponse
s@GetRevisionResponse' {} Maybe Text
a -> GetRevisionResponse
s {$sel:dataSetId:GetRevisionResponse' :: Maybe Text
dataSetId = Maybe Text
a} :: GetRevisionResponse)

-- | 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
-- 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.
-- 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.
getRevisionResponse_finalized :: Lens.Lens' GetRevisionResponse (Prelude.Maybe Prelude.Bool)
getRevisionResponse_finalized :: Lens' GetRevisionResponse (Maybe Bool)
getRevisionResponse_finalized = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRevisionResponse' {Maybe Bool
finalized :: Maybe Bool
$sel:finalized:GetRevisionResponse' :: GetRevisionResponse -> Maybe Bool
finalized} -> Maybe Bool
finalized) (\s :: GetRevisionResponse
s@GetRevisionResponse' {} Maybe Bool
a -> GetRevisionResponse
s {$sel:finalized:GetRevisionResponse' :: Maybe Bool
finalized = Maybe Bool
a} :: GetRevisionResponse)

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

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

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

-- | The date and time that the revision was revoked, in ISO 8601 format.
getRevisionResponse_revokedAt :: Lens.Lens' GetRevisionResponse (Prelude.Maybe Prelude.UTCTime)
getRevisionResponse_revokedAt :: Lens' GetRevisionResponse (Maybe UTCTime)
getRevisionResponse_revokedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRevisionResponse' {Maybe ISO8601
revokedAt :: Maybe ISO8601
$sel:revokedAt:GetRevisionResponse' :: GetRevisionResponse -> Maybe ISO8601
revokedAt} -> Maybe ISO8601
revokedAt) (\s :: GetRevisionResponse
s@GetRevisionResponse' {} Maybe ISO8601
a -> GetRevisionResponse
s {$sel:revokedAt:GetRevisionResponse' :: Maybe ISO8601
revokedAt = Maybe ISO8601
a} :: GetRevisionResponse) 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.
getRevisionResponse_sourceId :: Lens.Lens' GetRevisionResponse (Prelude.Maybe Prelude.Text)
getRevisionResponse_sourceId :: Lens' GetRevisionResponse (Maybe Text)
getRevisionResponse_sourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRevisionResponse' {Maybe Text
sourceId :: Maybe Text
$sel:sourceId:GetRevisionResponse' :: GetRevisionResponse -> Maybe Text
sourceId} -> Maybe Text
sourceId) (\s :: GetRevisionResponse
s@GetRevisionResponse' {} Maybe Text
a -> GetRevisionResponse
s {$sel:sourceId:GetRevisionResponse' :: Maybe Text
sourceId = Maybe Text
a} :: GetRevisionResponse)

-- | The tags for the revision.
getRevisionResponse_tags :: Lens.Lens' GetRevisionResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getRevisionResponse_tags :: Lens' GetRevisionResponse (Maybe (HashMap Text Text))
getRevisionResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRevisionResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetRevisionResponse' :: GetRevisionResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetRevisionResponse
s@GetRevisionResponse' {} Maybe (HashMap Text Text)
a -> GetRevisionResponse
s {$sel:tags:GetRevisionResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GetRevisionResponse) 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 and time that the revision was last updated, in ISO 8601
-- format.
getRevisionResponse_updatedAt :: Lens.Lens' GetRevisionResponse (Prelude.Maybe Prelude.UTCTime)
getRevisionResponse_updatedAt :: Lens' GetRevisionResponse (Maybe UTCTime)
getRevisionResponse_updatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRevisionResponse' {Maybe ISO8601
updatedAt :: Maybe ISO8601
$sel:updatedAt:GetRevisionResponse' :: GetRevisionResponse -> Maybe ISO8601
updatedAt} -> Maybe ISO8601
updatedAt) (\s :: GetRevisionResponse
s@GetRevisionResponse' {} Maybe ISO8601
a -> GetRevisionResponse
s {$sel:updatedAt:GetRevisionResponse' :: Maybe ISO8601
updatedAt = Maybe ISO8601
a} :: GetRevisionResponse) 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.
getRevisionResponse_httpStatus :: Lens.Lens' GetRevisionResponse Prelude.Int
getRevisionResponse_httpStatus :: Lens' GetRevisionResponse Int
getRevisionResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRevisionResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetRevisionResponse' :: GetRevisionResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetRevisionResponse
s@GetRevisionResponse' {} Int
a -> GetRevisionResponse
s {$sel:httpStatus:GetRevisionResponse' :: Int
httpStatus = Int
a} :: GetRevisionResponse)

instance Prelude.NFData GetRevisionResponse where
  rnf :: GetRevisionResponse -> ()
rnf GetRevisionResponse' {Int
Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe ISO8601
httpStatus :: Int
updatedAt :: Maybe ISO8601
tags :: Maybe (HashMap Text Text)
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:GetRevisionResponse' :: GetRevisionResponse -> Int
$sel:updatedAt:GetRevisionResponse' :: GetRevisionResponse -> Maybe ISO8601
$sel:tags:GetRevisionResponse' :: GetRevisionResponse -> Maybe (HashMap Text Text)
$sel:sourceId:GetRevisionResponse' :: GetRevisionResponse -> Maybe Text
$sel:revokedAt:GetRevisionResponse' :: GetRevisionResponse -> Maybe ISO8601
$sel:revoked:GetRevisionResponse' :: GetRevisionResponse -> Maybe Bool
$sel:revocationComment:GetRevisionResponse' :: GetRevisionResponse -> Maybe Text
$sel:id:GetRevisionResponse' :: GetRevisionResponse -> Maybe Text
$sel:finalized:GetRevisionResponse' :: GetRevisionResponse -> Maybe Bool
$sel:dataSetId:GetRevisionResponse' :: GetRevisionResponse -> Maybe Text
$sel:createdAt:GetRevisionResponse' :: GetRevisionResponse -> Maybe ISO8601
$sel:comment:GetRevisionResponse' :: GetRevisionResponse -> Maybe Text
$sel:arn:GetRevisionResponse' :: GetRevisionResponse -> 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 (HashMap Text Text)
tags
      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