{-# 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.SSM.DescribeDocumentPermission
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the permissions for a Amazon Web Services Systems Manager
-- document (SSM document). If you created the document, you are the owner.
-- If a document is shared, it can either be shared privately (by
-- specifying a user\'s Amazon Web Services account ID) or publicly
-- (/All/).
module Amazonka.SSM.DescribeDocumentPermission
  ( -- * Creating a Request
    DescribeDocumentPermission (..),
    newDescribeDocumentPermission,

    -- * Request Lenses
    describeDocumentPermission_maxResults,
    describeDocumentPermission_nextToken,
    describeDocumentPermission_name,
    describeDocumentPermission_permissionType,

    -- * Destructuring the Response
    DescribeDocumentPermissionResponse (..),
    newDescribeDocumentPermissionResponse,

    -- * Response Lenses
    describeDocumentPermissionResponse_accountIds,
    describeDocumentPermissionResponse_accountSharingInfoList,
    describeDocumentPermissionResponse_nextToken,
    describeDocumentPermissionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeDocumentPermission' smart constructor.
data DescribeDocumentPermission = DescribeDocumentPermission'
  { -- | The maximum number of items to return for this call. The call also
    -- returns a token that you can specify in a subsequent call to get the
    -- next set of results.
    DescribeDocumentPermission -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token for the next set of items to return. (You received this token
    -- from a previous call.)
    DescribeDocumentPermission -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the document for which you are the owner.
    DescribeDocumentPermission -> Text
name :: Prelude.Text,
    -- | The permission type for the document. The permission type can be
    -- /Share/.
    DescribeDocumentPermission -> DocumentPermissionType
permissionType :: DocumentPermissionType
  }
  deriving (DescribeDocumentPermission -> DescribeDocumentPermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDocumentPermission -> DescribeDocumentPermission -> Bool
$c/= :: DescribeDocumentPermission -> DescribeDocumentPermission -> Bool
== :: DescribeDocumentPermission -> DescribeDocumentPermission -> Bool
$c== :: DescribeDocumentPermission -> DescribeDocumentPermission -> Bool
Prelude.Eq, ReadPrec [DescribeDocumentPermission]
ReadPrec DescribeDocumentPermission
Int -> ReadS DescribeDocumentPermission
ReadS [DescribeDocumentPermission]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDocumentPermission]
$creadListPrec :: ReadPrec [DescribeDocumentPermission]
readPrec :: ReadPrec DescribeDocumentPermission
$creadPrec :: ReadPrec DescribeDocumentPermission
readList :: ReadS [DescribeDocumentPermission]
$creadList :: ReadS [DescribeDocumentPermission]
readsPrec :: Int -> ReadS DescribeDocumentPermission
$creadsPrec :: Int -> ReadS DescribeDocumentPermission
Prelude.Read, Int -> DescribeDocumentPermission -> ShowS
[DescribeDocumentPermission] -> ShowS
DescribeDocumentPermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDocumentPermission] -> ShowS
$cshowList :: [DescribeDocumentPermission] -> ShowS
show :: DescribeDocumentPermission -> String
$cshow :: DescribeDocumentPermission -> String
showsPrec :: Int -> DescribeDocumentPermission -> ShowS
$cshowsPrec :: Int -> DescribeDocumentPermission -> ShowS
Prelude.Show, forall x.
Rep DescribeDocumentPermission x -> DescribeDocumentPermission
forall x.
DescribeDocumentPermission -> Rep DescribeDocumentPermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeDocumentPermission x -> DescribeDocumentPermission
$cfrom :: forall x.
DescribeDocumentPermission -> Rep DescribeDocumentPermission x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDocumentPermission' 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:
--
-- 'maxResults', 'describeDocumentPermission_maxResults' - The maximum number of items to return for this call. The call also
-- returns a token that you can specify in a subsequent call to get the
-- next set of results.
--
-- 'nextToken', 'describeDocumentPermission_nextToken' - The token for the next set of items to return. (You received this token
-- from a previous call.)
--
-- 'name', 'describeDocumentPermission_name' - The name of the document for which you are the owner.
--
-- 'permissionType', 'describeDocumentPermission_permissionType' - The permission type for the document. The permission type can be
-- /Share/.
newDescribeDocumentPermission ::
  -- | 'name'
  Prelude.Text ->
  -- | 'permissionType'
  DocumentPermissionType ->
  DescribeDocumentPermission
newDescribeDocumentPermission :: Text -> DocumentPermissionType -> DescribeDocumentPermission
newDescribeDocumentPermission Text
pName_ DocumentPermissionType
pPermissionType_ =
  DescribeDocumentPermission'
    { $sel:maxResults:DescribeDocumentPermission' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeDocumentPermission' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DescribeDocumentPermission' :: Text
name = Text
pName_,
      $sel:permissionType:DescribeDocumentPermission' :: DocumentPermissionType
permissionType = DocumentPermissionType
pPermissionType_
    }

-- | The maximum number of items to return for this call. The call also
-- returns a token that you can specify in a subsequent call to get the
-- next set of results.
describeDocumentPermission_maxResults :: Lens.Lens' DescribeDocumentPermission (Prelude.Maybe Prelude.Natural)
describeDocumentPermission_maxResults :: Lens' DescribeDocumentPermission (Maybe Natural)
describeDocumentPermission_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDocumentPermission' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:DescribeDocumentPermission' :: DescribeDocumentPermission -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: DescribeDocumentPermission
s@DescribeDocumentPermission' {} Maybe Natural
a -> DescribeDocumentPermission
s {$sel:maxResults:DescribeDocumentPermission' :: Maybe Natural
maxResults = Maybe Natural
a} :: DescribeDocumentPermission)

-- | The token for the next set of items to return. (You received this token
-- from a previous call.)
describeDocumentPermission_nextToken :: Lens.Lens' DescribeDocumentPermission (Prelude.Maybe Prelude.Text)
describeDocumentPermission_nextToken :: Lens' DescribeDocumentPermission (Maybe Text)
describeDocumentPermission_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDocumentPermission' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeDocumentPermission' :: DescribeDocumentPermission -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeDocumentPermission
s@DescribeDocumentPermission' {} Maybe Text
a -> DescribeDocumentPermission
s {$sel:nextToken:DescribeDocumentPermission' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeDocumentPermission)

-- | The name of the document for which you are the owner.
describeDocumentPermission_name :: Lens.Lens' DescribeDocumentPermission Prelude.Text
describeDocumentPermission_name :: Lens' DescribeDocumentPermission Text
describeDocumentPermission_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDocumentPermission' {Text
name :: Text
$sel:name:DescribeDocumentPermission' :: DescribeDocumentPermission -> Text
name} -> Text
name) (\s :: DescribeDocumentPermission
s@DescribeDocumentPermission' {} Text
a -> DescribeDocumentPermission
s {$sel:name:DescribeDocumentPermission' :: Text
name = Text
a} :: DescribeDocumentPermission)

-- | The permission type for the document. The permission type can be
-- /Share/.
describeDocumentPermission_permissionType :: Lens.Lens' DescribeDocumentPermission DocumentPermissionType
describeDocumentPermission_permissionType :: Lens' DescribeDocumentPermission DocumentPermissionType
describeDocumentPermission_permissionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDocumentPermission' {DocumentPermissionType
permissionType :: DocumentPermissionType
$sel:permissionType:DescribeDocumentPermission' :: DescribeDocumentPermission -> DocumentPermissionType
permissionType} -> DocumentPermissionType
permissionType) (\s :: DescribeDocumentPermission
s@DescribeDocumentPermission' {} DocumentPermissionType
a -> DescribeDocumentPermission
s {$sel:permissionType:DescribeDocumentPermission' :: DocumentPermissionType
permissionType = DocumentPermissionType
a} :: DescribeDocumentPermission)

instance Core.AWSRequest DescribeDocumentPermission where
  type
    AWSResponse DescribeDocumentPermission =
      DescribeDocumentPermissionResponse
  request :: (Service -> Service)
-> DescribeDocumentPermission -> Request DescribeDocumentPermission
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 DescribeDocumentPermission
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeDocumentPermission)))
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 [AccountSharingInfo]
-> Maybe Text
-> Int
-> DescribeDocumentPermissionResponse
DescribeDocumentPermissionResponse'
            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
"AccountIds" 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
"AccountSharingInfoList"
                            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
"NextToken")
            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 DescribeDocumentPermission where
  hashWithSalt :: Int -> DescribeDocumentPermission -> Int
hashWithSalt Int
_salt DescribeDocumentPermission' {Maybe Natural
Maybe Text
Text
DocumentPermissionType
permissionType :: DocumentPermissionType
name :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:permissionType:DescribeDocumentPermission' :: DescribeDocumentPermission -> DocumentPermissionType
$sel:name:DescribeDocumentPermission' :: DescribeDocumentPermission -> Text
$sel:nextToken:DescribeDocumentPermission' :: DescribeDocumentPermission -> Maybe Text
$sel:maxResults:DescribeDocumentPermission' :: DescribeDocumentPermission -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DocumentPermissionType
permissionType

instance Prelude.NFData DescribeDocumentPermission where
  rnf :: DescribeDocumentPermission -> ()
rnf DescribeDocumentPermission' {Maybe Natural
Maybe Text
Text
DocumentPermissionType
permissionType :: DocumentPermissionType
name :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:permissionType:DescribeDocumentPermission' :: DescribeDocumentPermission -> DocumentPermissionType
$sel:name:DescribeDocumentPermission' :: DescribeDocumentPermission -> Text
$sel:nextToken:DescribeDocumentPermission' :: DescribeDocumentPermission -> Maybe Text
$sel:maxResults:DescribeDocumentPermission' :: DescribeDocumentPermission -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DocumentPermissionType
permissionType

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

instance Data.ToJSON DescribeDocumentPermission where
  toJSON :: DescribeDocumentPermission -> Value
toJSON DescribeDocumentPermission' {Maybe Natural
Maybe Text
Text
DocumentPermissionType
permissionType :: DocumentPermissionType
name :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:permissionType:DescribeDocumentPermission' :: DescribeDocumentPermission -> DocumentPermissionType
$sel:name:DescribeDocumentPermission' :: DescribeDocumentPermission -> Text
$sel:nextToken:DescribeDocumentPermission' :: DescribeDocumentPermission -> Maybe Text
$sel:maxResults:DescribeDocumentPermission' :: DescribeDocumentPermission -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxResults" 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 Natural
maxResults,
            (Key
"NextToken" 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
nextToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"PermissionType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= DocumentPermissionType
permissionType)
          ]
      )

instance Data.ToPath DescribeDocumentPermission where
  toPath :: DescribeDocumentPermission -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDescribeDocumentPermissionResponse' smart constructor.
data DescribeDocumentPermissionResponse = DescribeDocumentPermissionResponse'
  { -- | The account IDs that have permission to use this document. The ID can be
    -- either an Amazon Web Services account or /All/.
    DescribeDocumentPermissionResponse -> Maybe [Text]
accountIds :: Prelude.Maybe [Prelude.Text],
    -- | A list of Amazon Web Services accounts where the current document is
    -- shared and the version shared with each account.
    DescribeDocumentPermissionResponse -> Maybe [AccountSharingInfo]
accountSharingInfoList :: Prelude.Maybe [AccountSharingInfo],
    -- | The token for the next set of items to return. Use this token to get the
    -- next set of results.
    DescribeDocumentPermissionResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeDocumentPermissionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeDocumentPermissionResponse
-> DescribeDocumentPermissionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDocumentPermissionResponse
-> DescribeDocumentPermissionResponse -> Bool
$c/= :: DescribeDocumentPermissionResponse
-> DescribeDocumentPermissionResponse -> Bool
== :: DescribeDocumentPermissionResponse
-> DescribeDocumentPermissionResponse -> Bool
$c== :: DescribeDocumentPermissionResponse
-> DescribeDocumentPermissionResponse -> Bool
Prelude.Eq, ReadPrec [DescribeDocumentPermissionResponse]
ReadPrec DescribeDocumentPermissionResponse
Int -> ReadS DescribeDocumentPermissionResponse
ReadS [DescribeDocumentPermissionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDocumentPermissionResponse]
$creadListPrec :: ReadPrec [DescribeDocumentPermissionResponse]
readPrec :: ReadPrec DescribeDocumentPermissionResponse
$creadPrec :: ReadPrec DescribeDocumentPermissionResponse
readList :: ReadS [DescribeDocumentPermissionResponse]
$creadList :: ReadS [DescribeDocumentPermissionResponse]
readsPrec :: Int -> ReadS DescribeDocumentPermissionResponse
$creadsPrec :: Int -> ReadS DescribeDocumentPermissionResponse
Prelude.Read, Int -> DescribeDocumentPermissionResponse -> ShowS
[DescribeDocumentPermissionResponse] -> ShowS
DescribeDocumentPermissionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDocumentPermissionResponse] -> ShowS
$cshowList :: [DescribeDocumentPermissionResponse] -> ShowS
show :: DescribeDocumentPermissionResponse -> String
$cshow :: DescribeDocumentPermissionResponse -> String
showsPrec :: Int -> DescribeDocumentPermissionResponse -> ShowS
$cshowsPrec :: Int -> DescribeDocumentPermissionResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeDocumentPermissionResponse x
-> DescribeDocumentPermissionResponse
forall x.
DescribeDocumentPermissionResponse
-> Rep DescribeDocumentPermissionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeDocumentPermissionResponse x
-> DescribeDocumentPermissionResponse
$cfrom :: forall x.
DescribeDocumentPermissionResponse
-> Rep DescribeDocumentPermissionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDocumentPermissionResponse' 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:
--
-- 'accountIds', 'describeDocumentPermissionResponse_accountIds' - The account IDs that have permission to use this document. The ID can be
-- either an Amazon Web Services account or /All/.
--
-- 'accountSharingInfoList', 'describeDocumentPermissionResponse_accountSharingInfoList' - A list of Amazon Web Services accounts where the current document is
-- shared and the version shared with each account.
--
-- 'nextToken', 'describeDocumentPermissionResponse_nextToken' - The token for the next set of items to return. Use this token to get the
-- next set of results.
--
-- 'httpStatus', 'describeDocumentPermissionResponse_httpStatus' - The response's http status code.
newDescribeDocumentPermissionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeDocumentPermissionResponse
newDescribeDocumentPermissionResponse :: Int -> DescribeDocumentPermissionResponse
newDescribeDocumentPermissionResponse Int
pHttpStatus_ =
  DescribeDocumentPermissionResponse'
    { $sel:accountIds:DescribeDocumentPermissionResponse' :: Maybe [Text]
accountIds =
        forall a. Maybe a
Prelude.Nothing,
      $sel:accountSharingInfoList:DescribeDocumentPermissionResponse' :: Maybe [AccountSharingInfo]
accountSharingInfoList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeDocumentPermissionResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeDocumentPermissionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The account IDs that have permission to use this document. The ID can be
-- either an Amazon Web Services account or /All/.
describeDocumentPermissionResponse_accountIds :: Lens.Lens' DescribeDocumentPermissionResponse (Prelude.Maybe [Prelude.Text])
describeDocumentPermissionResponse_accountIds :: Lens' DescribeDocumentPermissionResponse (Maybe [Text])
describeDocumentPermissionResponse_accountIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDocumentPermissionResponse' {Maybe [Text]
accountIds :: Maybe [Text]
$sel:accountIds:DescribeDocumentPermissionResponse' :: DescribeDocumentPermissionResponse -> Maybe [Text]
accountIds} -> Maybe [Text]
accountIds) (\s :: DescribeDocumentPermissionResponse
s@DescribeDocumentPermissionResponse' {} Maybe [Text]
a -> DescribeDocumentPermissionResponse
s {$sel:accountIds:DescribeDocumentPermissionResponse' :: Maybe [Text]
accountIds = Maybe [Text]
a} :: DescribeDocumentPermissionResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A list of Amazon Web Services accounts where the current document is
-- shared and the version shared with each account.
describeDocumentPermissionResponse_accountSharingInfoList :: Lens.Lens' DescribeDocumentPermissionResponse (Prelude.Maybe [AccountSharingInfo])
describeDocumentPermissionResponse_accountSharingInfoList :: Lens'
  DescribeDocumentPermissionResponse (Maybe [AccountSharingInfo])
describeDocumentPermissionResponse_accountSharingInfoList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDocumentPermissionResponse' {Maybe [AccountSharingInfo]
accountSharingInfoList :: Maybe [AccountSharingInfo]
$sel:accountSharingInfoList:DescribeDocumentPermissionResponse' :: DescribeDocumentPermissionResponse -> Maybe [AccountSharingInfo]
accountSharingInfoList} -> Maybe [AccountSharingInfo]
accountSharingInfoList) (\s :: DescribeDocumentPermissionResponse
s@DescribeDocumentPermissionResponse' {} Maybe [AccountSharingInfo]
a -> DescribeDocumentPermissionResponse
s {$sel:accountSharingInfoList:DescribeDocumentPermissionResponse' :: Maybe [AccountSharingInfo]
accountSharingInfoList = Maybe [AccountSharingInfo]
a} :: DescribeDocumentPermissionResponse) 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 token for the next set of items to return. Use this token to get the
-- next set of results.
describeDocumentPermissionResponse_nextToken :: Lens.Lens' DescribeDocumentPermissionResponse (Prelude.Maybe Prelude.Text)
describeDocumentPermissionResponse_nextToken :: Lens' DescribeDocumentPermissionResponse (Maybe Text)
describeDocumentPermissionResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDocumentPermissionResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeDocumentPermissionResponse' :: DescribeDocumentPermissionResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeDocumentPermissionResponse
s@DescribeDocumentPermissionResponse' {} Maybe Text
a -> DescribeDocumentPermissionResponse
s {$sel:nextToken:DescribeDocumentPermissionResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeDocumentPermissionResponse)

-- | The response's http status code.
describeDocumentPermissionResponse_httpStatus :: Lens.Lens' DescribeDocumentPermissionResponse Prelude.Int
describeDocumentPermissionResponse_httpStatus :: Lens' DescribeDocumentPermissionResponse Int
describeDocumentPermissionResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDocumentPermissionResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeDocumentPermissionResponse' :: DescribeDocumentPermissionResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeDocumentPermissionResponse
s@DescribeDocumentPermissionResponse' {} Int
a -> DescribeDocumentPermissionResponse
s {$sel:httpStatus:DescribeDocumentPermissionResponse' :: Int
httpStatus = Int
a} :: DescribeDocumentPermissionResponse)

instance
  Prelude.NFData
    DescribeDocumentPermissionResponse
  where
  rnf :: DescribeDocumentPermissionResponse -> ()
rnf DescribeDocumentPermissionResponse' {Int
Maybe [Text]
Maybe [AccountSharingInfo]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
accountSharingInfoList :: Maybe [AccountSharingInfo]
accountIds :: Maybe [Text]
$sel:httpStatus:DescribeDocumentPermissionResponse' :: DescribeDocumentPermissionResponse -> Int
$sel:nextToken:DescribeDocumentPermissionResponse' :: DescribeDocumentPermissionResponse -> Maybe Text
$sel:accountSharingInfoList:DescribeDocumentPermissionResponse' :: DescribeDocumentPermissionResponse -> Maybe [AccountSharingInfo]
$sel:accountIds:DescribeDocumentPermissionResponse' :: DescribeDocumentPermissionResponse -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
accountIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AccountSharingInfo]
accountSharingInfoList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus