{-# 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.RevokeRevision
-- 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 revokes subscribers\' access to a revision.
module Amazonka.DataExchange.RevokeRevision
  ( -- * Creating a Request
    RevokeRevision (..),
    newRevokeRevision,

    -- * Request Lenses
    revokeRevision_dataSetId,
    revokeRevision_revisionId,
    revokeRevision_revocationComment,

    -- * Destructuring the Response
    RevokeRevisionResponse (..),
    newRevokeRevisionResponse,

    -- * Response Lenses
    revokeRevisionResponse_arn,
    revokeRevisionResponse_comment,
    revokeRevisionResponse_createdAt,
    revokeRevisionResponse_dataSetId,
    revokeRevisionResponse_finalized,
    revokeRevisionResponse_id,
    revokeRevisionResponse_revocationComment,
    revokeRevisionResponse_revoked,
    revokeRevisionResponse_revokedAt,
    revokeRevisionResponse_sourceId,
    revokeRevisionResponse_updatedAt,
    revokeRevisionResponse_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:/ 'newRevokeRevision' smart constructor.
data RevokeRevision = RevokeRevision'
  { -- | The unique identifier for a data set.
    RevokeRevision -> Text
dataSetId :: Prelude.Text,
    -- | The unique identifier for a revision.
    RevokeRevision -> Text
revisionId :: Prelude.Text,
    -- | A required comment to inform subscribers of the reason their access to
    -- the revision was revoked.
    RevokeRevision -> Text
revocationComment :: Prelude.Text
  }
  deriving (RevokeRevision -> RevokeRevision -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RevokeRevision -> RevokeRevision -> Bool
$c/= :: RevokeRevision -> RevokeRevision -> Bool
== :: RevokeRevision -> RevokeRevision -> Bool
$c== :: RevokeRevision -> RevokeRevision -> Bool
Prelude.Eq, ReadPrec [RevokeRevision]
ReadPrec RevokeRevision
Int -> ReadS RevokeRevision
ReadS [RevokeRevision]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RevokeRevision]
$creadListPrec :: ReadPrec [RevokeRevision]
readPrec :: ReadPrec RevokeRevision
$creadPrec :: ReadPrec RevokeRevision
readList :: ReadS [RevokeRevision]
$creadList :: ReadS [RevokeRevision]
readsPrec :: Int -> ReadS RevokeRevision
$creadsPrec :: Int -> ReadS RevokeRevision
Prelude.Read, Int -> RevokeRevision -> ShowS
[RevokeRevision] -> ShowS
RevokeRevision -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RevokeRevision] -> ShowS
$cshowList :: [RevokeRevision] -> ShowS
show :: RevokeRevision -> String
$cshow :: RevokeRevision -> String
showsPrec :: Int -> RevokeRevision -> ShowS
$cshowsPrec :: Int -> RevokeRevision -> ShowS
Prelude.Show, forall x. Rep RevokeRevision x -> RevokeRevision
forall x. RevokeRevision -> Rep RevokeRevision x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RevokeRevision x -> RevokeRevision
$cfrom :: forall x. RevokeRevision -> Rep RevokeRevision x
Prelude.Generic)

-- |
-- Create a value of 'RevokeRevision' 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', 'revokeRevision_dataSetId' - The unique identifier for a data set.
--
-- 'revisionId', 'revokeRevision_revisionId' - The unique identifier for a revision.
--
-- 'revocationComment', 'revokeRevision_revocationComment' - A required comment to inform subscribers of the reason their access to
-- the revision was revoked.
newRevokeRevision ::
  -- | 'dataSetId'
  Prelude.Text ->
  -- | 'revisionId'
  Prelude.Text ->
  -- | 'revocationComment'
  Prelude.Text ->
  RevokeRevision
newRevokeRevision :: Text -> Text -> Text -> RevokeRevision
newRevokeRevision
  Text
pDataSetId_
  Text
pRevisionId_
  Text
pRevocationComment_ =
    RevokeRevision'
      { $sel:dataSetId:RevokeRevision' :: Text
dataSetId = Text
pDataSetId_,
        $sel:revisionId:RevokeRevision' :: Text
revisionId = Text
pRevisionId_,
        $sel:revocationComment:RevokeRevision' :: Text
revocationComment = Text
pRevocationComment_
      }

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

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

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

instance Core.AWSRequest RevokeRevision where
  type
    AWSResponse RevokeRevision =
      RevokeRevisionResponse
  request :: (Service -> Service) -> RevokeRevision -> Request RevokeRevision
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy RevokeRevision
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse RevokeRevision)))
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
-> RevokeRevisionResponse
RevokeRevisionResponse'
            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 RevokeRevision where
  hashWithSalt :: Int -> RevokeRevision -> Int
hashWithSalt Int
_salt RevokeRevision' {Text
revocationComment :: Text
revisionId :: Text
dataSetId :: Text
$sel:revocationComment:RevokeRevision' :: RevokeRevision -> Text
$sel:revisionId:RevokeRevision' :: RevokeRevision -> Text
$sel:dataSetId:RevokeRevision' :: RevokeRevision -> 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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
revocationComment

instance Prelude.NFData RevokeRevision where
  rnf :: RevokeRevision -> ()
rnf RevokeRevision' {Text
revocationComment :: Text
revisionId :: Text
dataSetId :: Text
$sel:revocationComment:RevokeRevision' :: RevokeRevision -> Text
$sel:revisionId:RevokeRevision' :: RevokeRevision -> Text
$sel:dataSetId:RevokeRevision' :: RevokeRevision -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
revocationComment

instance Data.ToHeaders RevokeRevision where
  toHeaders :: RevokeRevision -> 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 RevokeRevision where
  toJSON :: RevokeRevision -> Value
toJSON RevokeRevision' {Text
revocationComment :: Text
revisionId :: Text
dataSetId :: Text
$sel:revocationComment:RevokeRevision' :: RevokeRevision -> Text
$sel:revisionId:RevokeRevision' :: RevokeRevision -> Text
$sel:dataSetId:RevokeRevision' :: RevokeRevision -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"RevocationComment" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
revocationComment)
          ]
      )

instance Data.ToPath RevokeRevision where
  toPath :: RevokeRevision -> ByteString
toPath RevokeRevision' {Text
revocationComment :: Text
revisionId :: Text
dataSetId :: Text
$sel:revocationComment:RevokeRevision' :: RevokeRevision -> Text
$sel:revisionId:RevokeRevision' :: RevokeRevision -> Text
$sel:dataSetId:RevokeRevision' :: RevokeRevision -> 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,
        ByteString
"/revoke"
      ]

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

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

-- |
-- Create a value of 'RevokeRevisionResponse' 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', 'revokeRevisionResponse_arn' - The ARN for the revision.
--
-- 'comment', 'revokeRevisionResponse_comment' - An optional comment about the revision.
--
-- 'createdAt', 'revokeRevisionResponse_createdAt' - The date and time that the revision was created, in ISO 8601 format.
--
-- 'dataSetId', 'revokeRevisionResponse_dataSetId' - The unique identifier for the data set associated with the data set
-- revision.
--
-- 'finalized', 'revokeRevisionResponse_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', 'revokeRevisionResponse_id' - The unique identifier for the revision.
--
-- 'revocationComment', 'revokeRevisionResponse_revocationComment' - A required comment to inform subscribers of the reason their access to
-- the revision was revoked.
--
-- 'revoked', 'revokeRevisionResponse_revoked' - A status indicating that subscribers\' access to the revision was
-- revoked.
--
-- 'revokedAt', 'revokeRevisionResponse_revokedAt' - The date and time that the revision was revoked, in ISO 8601 format.
--
-- 'sourceId', 'revokeRevisionResponse_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', 'revokeRevisionResponse_updatedAt' - The date and time that the revision was last updated, in ISO 8601
-- format.
--
-- 'httpStatus', 'revokeRevisionResponse_httpStatus' - The response's http status code.
newRevokeRevisionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RevokeRevisionResponse
newRevokeRevisionResponse :: Int -> RevokeRevisionResponse
newRevokeRevisionResponse Int
pHttpStatus_ =
  RevokeRevisionResponse'
    { $sel:arn:RevokeRevisionResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:comment:RevokeRevisionResponse' :: Maybe Text
comment = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:RevokeRevisionResponse' :: Maybe ISO8601
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:dataSetId:RevokeRevisionResponse' :: Maybe Text
dataSetId = forall a. Maybe a
Prelude.Nothing,
      $sel:finalized:RevokeRevisionResponse' :: Maybe Bool
finalized = forall a. Maybe a
Prelude.Nothing,
      $sel:id:RevokeRevisionResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:revocationComment:RevokeRevisionResponse' :: Maybe Text
revocationComment = forall a. Maybe a
Prelude.Nothing,
      $sel:revoked:RevokeRevisionResponse' :: Maybe Bool
revoked = forall a. Maybe a
Prelude.Nothing,
      $sel:revokedAt:RevokeRevisionResponse' :: Maybe ISO8601
revokedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceId:RevokeRevisionResponse' :: Maybe Text
sourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedAt:RevokeRevisionResponse' :: Maybe ISO8601
updatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RevokeRevisionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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

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

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

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

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

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

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

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