{-# 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.Transfer.DescribeAccess
-- 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 access that is assigned to the specific file transfer
-- protocol-enabled server, as identified by its @ServerId@ property and
-- its @ExternalId@.
--
-- The response from this call returns the properties of the access that is
-- associated with the @ServerId@ value that was specified.
module Amazonka.Transfer.DescribeAccess
  ( -- * Creating a Request
    DescribeAccess (..),
    newDescribeAccess,

    -- * Request Lenses
    describeAccess_serverId,
    describeAccess_externalId,

    -- * Destructuring the Response
    DescribeAccessResponse (..),
    newDescribeAccessResponse,

    -- * Response Lenses
    describeAccessResponse_httpStatus,
    describeAccessResponse_serverId,
    describeAccessResponse_access,
  )
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.Transfer.Types

-- | /See:/ 'newDescribeAccess' smart constructor.
data DescribeAccess = DescribeAccess'
  { -- | A system-assigned unique identifier for a server that has this access
    -- assigned.
    DescribeAccess -> Text
serverId :: Prelude.Text,
    -- | A unique identifier that is required to identify specific groups within
    -- your directory. The users of the group that you associate have access to
    -- your Amazon S3 or Amazon EFS resources over the enabled protocols using
    -- Transfer Family. If you know the group name, you can view the SID values
    -- by running the following command using Windows PowerShell.
    --
    -- @Get-ADGroup -Filter {samAccountName -like \"@/@YourGroupName@/@*\"} -Properties * | Select SamAccountName,ObjectSid@
    --
    -- In that command, replace /YourGroupName/ with the name of your Active
    -- Directory group.
    --
    -- The regular expression used to validate this parameter is a string of
    -- characters consisting of uppercase and lowercase alphanumeric characters
    -- with no spaces. You can also include underscores or any of the following
    -- characters: =,.\@:\/-
    DescribeAccess -> Text
externalId :: Prelude.Text
  }
  deriving (DescribeAccess -> DescribeAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAccess -> DescribeAccess -> Bool
$c/= :: DescribeAccess -> DescribeAccess -> Bool
== :: DescribeAccess -> DescribeAccess -> Bool
$c== :: DescribeAccess -> DescribeAccess -> Bool
Prelude.Eq, ReadPrec [DescribeAccess]
ReadPrec DescribeAccess
Int -> ReadS DescribeAccess
ReadS [DescribeAccess]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAccess]
$creadListPrec :: ReadPrec [DescribeAccess]
readPrec :: ReadPrec DescribeAccess
$creadPrec :: ReadPrec DescribeAccess
readList :: ReadS [DescribeAccess]
$creadList :: ReadS [DescribeAccess]
readsPrec :: Int -> ReadS DescribeAccess
$creadsPrec :: Int -> ReadS DescribeAccess
Prelude.Read, Int -> DescribeAccess -> ShowS
[DescribeAccess] -> ShowS
DescribeAccess -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAccess] -> ShowS
$cshowList :: [DescribeAccess] -> ShowS
show :: DescribeAccess -> String
$cshow :: DescribeAccess -> String
showsPrec :: Int -> DescribeAccess -> ShowS
$cshowsPrec :: Int -> DescribeAccess -> ShowS
Prelude.Show, forall x. Rep DescribeAccess x -> DescribeAccess
forall x. DescribeAccess -> Rep DescribeAccess x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeAccess x -> DescribeAccess
$cfrom :: forall x. DescribeAccess -> Rep DescribeAccess x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAccess' 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:
--
-- 'serverId', 'describeAccess_serverId' - A system-assigned unique identifier for a server that has this access
-- assigned.
--
-- 'externalId', 'describeAccess_externalId' - A unique identifier that is required to identify specific groups within
-- your directory. The users of the group that you associate have access to
-- your Amazon S3 or Amazon EFS resources over the enabled protocols using
-- Transfer Family. If you know the group name, you can view the SID values
-- by running the following command using Windows PowerShell.
--
-- @Get-ADGroup -Filter {samAccountName -like \"@/@YourGroupName@/@*\"} -Properties * | Select SamAccountName,ObjectSid@
--
-- In that command, replace /YourGroupName/ with the name of your Active
-- Directory group.
--
-- The regular expression used to validate this parameter is a string of
-- characters consisting of uppercase and lowercase alphanumeric characters
-- with no spaces. You can also include underscores or any of the following
-- characters: =,.\@:\/-
newDescribeAccess ::
  -- | 'serverId'
  Prelude.Text ->
  -- | 'externalId'
  Prelude.Text ->
  DescribeAccess
newDescribeAccess :: Text -> Text -> DescribeAccess
newDescribeAccess Text
pServerId_ Text
pExternalId_ =
  DescribeAccess'
    { $sel:serverId:DescribeAccess' :: Text
serverId = Text
pServerId_,
      $sel:externalId:DescribeAccess' :: Text
externalId = Text
pExternalId_
    }

-- | A system-assigned unique identifier for a server that has this access
-- assigned.
describeAccess_serverId :: Lens.Lens' DescribeAccess Prelude.Text
describeAccess_serverId :: Lens' DescribeAccess Text
describeAccess_serverId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAccess' {Text
serverId :: Text
$sel:serverId:DescribeAccess' :: DescribeAccess -> Text
serverId} -> Text
serverId) (\s :: DescribeAccess
s@DescribeAccess' {} Text
a -> DescribeAccess
s {$sel:serverId:DescribeAccess' :: Text
serverId = Text
a} :: DescribeAccess)

-- | A unique identifier that is required to identify specific groups within
-- your directory. The users of the group that you associate have access to
-- your Amazon S3 or Amazon EFS resources over the enabled protocols using
-- Transfer Family. If you know the group name, you can view the SID values
-- by running the following command using Windows PowerShell.
--
-- @Get-ADGroup -Filter {samAccountName -like \"@/@YourGroupName@/@*\"} -Properties * | Select SamAccountName,ObjectSid@
--
-- In that command, replace /YourGroupName/ with the name of your Active
-- Directory group.
--
-- The regular expression used to validate this parameter is a string of
-- characters consisting of uppercase and lowercase alphanumeric characters
-- with no spaces. You can also include underscores or any of the following
-- characters: =,.\@:\/-
describeAccess_externalId :: Lens.Lens' DescribeAccess Prelude.Text
describeAccess_externalId :: Lens' DescribeAccess Text
describeAccess_externalId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAccess' {Text
externalId :: Text
$sel:externalId:DescribeAccess' :: DescribeAccess -> Text
externalId} -> Text
externalId) (\s :: DescribeAccess
s@DescribeAccess' {} Text
a -> DescribeAccess
s {$sel:externalId:DescribeAccess' :: Text
externalId = Text
a} :: DescribeAccess)

instance Core.AWSRequest DescribeAccess where
  type
    AWSResponse DescribeAccess =
      DescribeAccessResponse
  request :: (Service -> Service) -> DescribeAccess -> Request DescribeAccess
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 DescribeAccess
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeAccess)))
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 ->
          Int -> Text -> DescribedAccess -> DescribeAccessResponse
DescribeAccessResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"ServerId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"Access")
      )

instance Prelude.Hashable DescribeAccess where
  hashWithSalt :: Int -> DescribeAccess -> Int
hashWithSalt Int
_salt DescribeAccess' {Text
externalId :: Text
serverId :: Text
$sel:externalId:DescribeAccess' :: DescribeAccess -> Text
$sel:serverId:DescribeAccess' :: DescribeAccess -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serverId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
externalId

instance Prelude.NFData DescribeAccess where
  rnf :: DescribeAccess -> ()
rnf DescribeAccess' {Text
externalId :: Text
serverId :: Text
$sel:externalId:DescribeAccess' :: DescribeAccess -> Text
$sel:serverId:DescribeAccess' :: DescribeAccess -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
serverId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
externalId

instance Data.ToHeaders DescribeAccess where
  toHeaders :: DescribeAccess -> 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
"TransferService.DescribeAccess" ::
                          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 DescribeAccess where
  toJSON :: DescribeAccess -> Value
toJSON DescribeAccess' {Text
externalId :: Text
serverId :: Text
$sel:externalId:DescribeAccess' :: DescribeAccess -> Text
$sel:serverId:DescribeAccess' :: DescribeAccess -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"ServerId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serverId),
            forall a. a -> Maybe a
Prelude.Just (Key
"ExternalId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
externalId)
          ]
      )

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

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

-- | /See:/ 'newDescribeAccessResponse' smart constructor.
data DescribeAccessResponse = DescribeAccessResponse'
  { -- | The response's http status code.
    DescribeAccessResponse -> Int
httpStatus :: Prelude.Int,
    -- | A system-assigned unique identifier for a server that has this access
    -- assigned.
    DescribeAccessResponse -> Text
serverId :: Prelude.Text,
    -- | The external identifier of the server that the access is attached to.
    DescribeAccessResponse -> DescribedAccess
access :: DescribedAccess
  }
  deriving (DescribeAccessResponse -> DescribeAccessResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAccessResponse -> DescribeAccessResponse -> Bool
$c/= :: DescribeAccessResponse -> DescribeAccessResponse -> Bool
== :: DescribeAccessResponse -> DescribeAccessResponse -> Bool
$c== :: DescribeAccessResponse -> DescribeAccessResponse -> Bool
Prelude.Eq, ReadPrec [DescribeAccessResponse]
ReadPrec DescribeAccessResponse
Int -> ReadS DescribeAccessResponse
ReadS [DescribeAccessResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAccessResponse]
$creadListPrec :: ReadPrec [DescribeAccessResponse]
readPrec :: ReadPrec DescribeAccessResponse
$creadPrec :: ReadPrec DescribeAccessResponse
readList :: ReadS [DescribeAccessResponse]
$creadList :: ReadS [DescribeAccessResponse]
readsPrec :: Int -> ReadS DescribeAccessResponse
$creadsPrec :: Int -> ReadS DescribeAccessResponse
Prelude.Read, Int -> DescribeAccessResponse -> ShowS
[DescribeAccessResponse] -> ShowS
DescribeAccessResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAccessResponse] -> ShowS
$cshowList :: [DescribeAccessResponse] -> ShowS
show :: DescribeAccessResponse -> String
$cshow :: DescribeAccessResponse -> String
showsPrec :: Int -> DescribeAccessResponse -> ShowS
$cshowsPrec :: Int -> DescribeAccessResponse -> ShowS
Prelude.Show, forall x. Rep DescribeAccessResponse x -> DescribeAccessResponse
forall x. DescribeAccessResponse -> Rep DescribeAccessResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeAccessResponse x -> DescribeAccessResponse
$cfrom :: forall x. DescribeAccessResponse -> Rep DescribeAccessResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAccessResponse' 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:
--
-- 'httpStatus', 'describeAccessResponse_httpStatus' - The response's http status code.
--
-- 'serverId', 'describeAccessResponse_serverId' - A system-assigned unique identifier for a server that has this access
-- assigned.
--
-- 'access', 'describeAccessResponse_access' - The external identifier of the server that the access is attached to.
newDescribeAccessResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'serverId'
  Prelude.Text ->
  -- | 'access'
  DescribedAccess ->
  DescribeAccessResponse
newDescribeAccessResponse :: Int -> Text -> DescribedAccess -> DescribeAccessResponse
newDescribeAccessResponse
  Int
pHttpStatus_
  Text
pServerId_
  DescribedAccess
pAccess_ =
    DescribeAccessResponse'
      { $sel:httpStatus:DescribeAccessResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:serverId:DescribeAccessResponse' :: Text
serverId = Text
pServerId_,
        $sel:access:DescribeAccessResponse' :: DescribedAccess
access = DescribedAccess
pAccess_
      }

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

-- | A system-assigned unique identifier for a server that has this access
-- assigned.
describeAccessResponse_serverId :: Lens.Lens' DescribeAccessResponse Prelude.Text
describeAccessResponse_serverId :: Lens' DescribeAccessResponse Text
describeAccessResponse_serverId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAccessResponse' {Text
serverId :: Text
$sel:serverId:DescribeAccessResponse' :: DescribeAccessResponse -> Text
serverId} -> Text
serverId) (\s :: DescribeAccessResponse
s@DescribeAccessResponse' {} Text
a -> DescribeAccessResponse
s {$sel:serverId:DescribeAccessResponse' :: Text
serverId = Text
a} :: DescribeAccessResponse)

-- | The external identifier of the server that the access is attached to.
describeAccessResponse_access :: Lens.Lens' DescribeAccessResponse DescribedAccess
describeAccessResponse_access :: Lens' DescribeAccessResponse DescribedAccess
describeAccessResponse_access = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAccessResponse' {DescribedAccess
access :: DescribedAccess
$sel:access:DescribeAccessResponse' :: DescribeAccessResponse -> DescribedAccess
access} -> DescribedAccess
access) (\s :: DescribeAccessResponse
s@DescribeAccessResponse' {} DescribedAccess
a -> DescribeAccessResponse
s {$sel:access:DescribeAccessResponse' :: DescribedAccess
access = DescribedAccess
a} :: DescribeAccessResponse)

instance Prelude.NFData DescribeAccessResponse where
  rnf :: DescribeAccessResponse -> ()
rnf DescribeAccessResponse' {Int
Text
DescribedAccess
access :: DescribedAccess
serverId :: Text
httpStatus :: Int
$sel:access:DescribeAccessResponse' :: DescribeAccessResponse -> DescribedAccess
$sel:serverId:DescribeAccessResponse' :: DescribeAccessResponse -> Text
$sel:httpStatus:DescribeAccessResponse' :: DescribeAccessResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serverId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DescribedAccess
access