{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.ListedAccess
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Transfer.Types.ListedAccess 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 Amazonka.Transfer.Types.HomeDirectoryType

-- | Lists the properties for one or more specified associated accesses.
--
-- /See:/ 'newListedAccess' smart constructor.
data ListedAccess = ListedAccess'
  { -- | 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: =,.\@:\/-
    ListedAccess -> Maybe Text
externalId :: Prelude.Maybe Prelude.Text,
    -- | The landing directory (folder) for a user when they log in to the server
    -- using the client.
    --
    -- A @HomeDirectory@ example is @\/bucket_name\/home\/mydirectory@.
    ListedAccess -> Maybe Text
homeDirectory :: Prelude.Maybe Prelude.Text,
    -- | The type of landing directory (folder) that you want your users\' home
    -- directory to be when they log in to the server. If you set it to @PATH@,
    -- the user will see the absolute Amazon S3 bucket or EFS paths as is in
    -- their file transfer protocol clients. If you set it @LOGICAL@, you need
    -- to provide mappings in the @HomeDirectoryMappings@ for how you want to
    -- make Amazon S3 or Amazon EFS paths visible to your users.
    ListedAccess -> Maybe HomeDirectoryType
homeDirectoryType :: Prelude.Maybe HomeDirectoryType,
    -- | The Amazon Resource Name (ARN) of the Identity and Access Management
    -- (IAM) role that controls your users\' access to your Amazon S3 bucket or
    -- Amazon EFS file system. The policies attached to this role determine the
    -- level of access that you want to provide your users when transferring
    -- files into and out of your Amazon S3 bucket or Amazon EFS file system.
    -- The IAM role should also contain a trust relationship that allows the
    -- server to access your resources when servicing your users\' transfer
    -- requests.
    ListedAccess -> Maybe Text
role' :: Prelude.Maybe Prelude.Text
  }
  deriving (ListedAccess -> ListedAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListedAccess -> ListedAccess -> Bool
$c/= :: ListedAccess -> ListedAccess -> Bool
== :: ListedAccess -> ListedAccess -> Bool
$c== :: ListedAccess -> ListedAccess -> Bool
Prelude.Eq, ReadPrec [ListedAccess]
ReadPrec ListedAccess
Int -> ReadS ListedAccess
ReadS [ListedAccess]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListedAccess]
$creadListPrec :: ReadPrec [ListedAccess]
readPrec :: ReadPrec ListedAccess
$creadPrec :: ReadPrec ListedAccess
readList :: ReadS [ListedAccess]
$creadList :: ReadS [ListedAccess]
readsPrec :: Int -> ReadS ListedAccess
$creadsPrec :: Int -> ReadS ListedAccess
Prelude.Read, Int -> ListedAccess -> ShowS
[ListedAccess] -> ShowS
ListedAccess -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListedAccess] -> ShowS
$cshowList :: [ListedAccess] -> ShowS
show :: ListedAccess -> String
$cshow :: ListedAccess -> String
showsPrec :: Int -> ListedAccess -> ShowS
$cshowsPrec :: Int -> ListedAccess -> ShowS
Prelude.Show, forall x. Rep ListedAccess x -> ListedAccess
forall x. ListedAccess -> Rep ListedAccess x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListedAccess x -> ListedAccess
$cfrom :: forall x. ListedAccess -> Rep ListedAccess x
Prelude.Generic)

-- |
-- Create a value of 'ListedAccess' 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:
--
-- 'externalId', 'listedAccess_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: =,.\@:\/-
--
-- 'homeDirectory', 'listedAccess_homeDirectory' - The landing directory (folder) for a user when they log in to the server
-- using the client.
--
-- A @HomeDirectory@ example is @\/bucket_name\/home\/mydirectory@.
--
-- 'homeDirectoryType', 'listedAccess_homeDirectoryType' - The type of landing directory (folder) that you want your users\' home
-- directory to be when they log in to the server. If you set it to @PATH@,
-- the user will see the absolute Amazon S3 bucket or EFS paths as is in
-- their file transfer protocol clients. If you set it @LOGICAL@, you need
-- to provide mappings in the @HomeDirectoryMappings@ for how you want to
-- make Amazon S3 or Amazon EFS paths visible to your users.
--
-- 'role'', 'listedAccess_role' - The Amazon Resource Name (ARN) of the Identity and Access Management
-- (IAM) role that controls your users\' access to your Amazon S3 bucket or
-- Amazon EFS file system. The policies attached to this role determine the
-- level of access that you want to provide your users when transferring
-- files into and out of your Amazon S3 bucket or Amazon EFS file system.
-- The IAM role should also contain a trust relationship that allows the
-- server to access your resources when servicing your users\' transfer
-- requests.
newListedAccess ::
  ListedAccess
newListedAccess :: ListedAccess
newListedAccess =
  ListedAccess'
    { $sel:externalId:ListedAccess' :: Maybe Text
externalId = forall a. Maybe a
Prelude.Nothing,
      $sel:homeDirectory:ListedAccess' :: Maybe Text
homeDirectory = forall a. Maybe a
Prelude.Nothing,
      $sel:homeDirectoryType:ListedAccess' :: Maybe HomeDirectoryType
homeDirectoryType = forall a. Maybe a
Prelude.Nothing,
      $sel:role':ListedAccess' :: Maybe Text
role' = forall a. Maybe a
Prelude.Nothing
    }

-- | 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: =,.\@:\/-
listedAccess_externalId :: Lens.Lens' ListedAccess (Prelude.Maybe Prelude.Text)
listedAccess_externalId :: Lens' ListedAccess (Maybe Text)
listedAccess_externalId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListedAccess' {Maybe Text
externalId :: Maybe Text
$sel:externalId:ListedAccess' :: ListedAccess -> Maybe Text
externalId} -> Maybe Text
externalId) (\s :: ListedAccess
s@ListedAccess' {} Maybe Text
a -> ListedAccess
s {$sel:externalId:ListedAccess' :: Maybe Text
externalId = Maybe Text
a} :: ListedAccess)

-- | The landing directory (folder) for a user when they log in to the server
-- using the client.
--
-- A @HomeDirectory@ example is @\/bucket_name\/home\/mydirectory@.
listedAccess_homeDirectory :: Lens.Lens' ListedAccess (Prelude.Maybe Prelude.Text)
listedAccess_homeDirectory :: Lens' ListedAccess (Maybe Text)
listedAccess_homeDirectory = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListedAccess' {Maybe Text
homeDirectory :: Maybe Text
$sel:homeDirectory:ListedAccess' :: ListedAccess -> Maybe Text
homeDirectory} -> Maybe Text
homeDirectory) (\s :: ListedAccess
s@ListedAccess' {} Maybe Text
a -> ListedAccess
s {$sel:homeDirectory:ListedAccess' :: Maybe Text
homeDirectory = Maybe Text
a} :: ListedAccess)

-- | The type of landing directory (folder) that you want your users\' home
-- directory to be when they log in to the server. If you set it to @PATH@,
-- the user will see the absolute Amazon S3 bucket or EFS paths as is in
-- their file transfer protocol clients. If you set it @LOGICAL@, you need
-- to provide mappings in the @HomeDirectoryMappings@ for how you want to
-- make Amazon S3 or Amazon EFS paths visible to your users.
listedAccess_homeDirectoryType :: Lens.Lens' ListedAccess (Prelude.Maybe HomeDirectoryType)
listedAccess_homeDirectoryType :: Lens' ListedAccess (Maybe HomeDirectoryType)
listedAccess_homeDirectoryType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListedAccess' {Maybe HomeDirectoryType
homeDirectoryType :: Maybe HomeDirectoryType
$sel:homeDirectoryType:ListedAccess' :: ListedAccess -> Maybe HomeDirectoryType
homeDirectoryType} -> Maybe HomeDirectoryType
homeDirectoryType) (\s :: ListedAccess
s@ListedAccess' {} Maybe HomeDirectoryType
a -> ListedAccess
s {$sel:homeDirectoryType:ListedAccess' :: Maybe HomeDirectoryType
homeDirectoryType = Maybe HomeDirectoryType
a} :: ListedAccess)

-- | The Amazon Resource Name (ARN) of the Identity and Access Management
-- (IAM) role that controls your users\' access to your Amazon S3 bucket or
-- Amazon EFS file system. The policies attached to this role determine the
-- level of access that you want to provide your users when transferring
-- files into and out of your Amazon S3 bucket or Amazon EFS file system.
-- The IAM role should also contain a trust relationship that allows the
-- server to access your resources when servicing your users\' transfer
-- requests.
listedAccess_role :: Lens.Lens' ListedAccess (Prelude.Maybe Prelude.Text)
listedAccess_role :: Lens' ListedAccess (Maybe Text)
listedAccess_role = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListedAccess' {Maybe Text
role' :: Maybe Text
$sel:role':ListedAccess' :: ListedAccess -> Maybe Text
role'} -> Maybe Text
role') (\s :: ListedAccess
s@ListedAccess' {} Maybe Text
a -> ListedAccess
s {$sel:role':ListedAccess' :: Maybe Text
role' = Maybe Text
a} :: ListedAccess)

instance Data.FromJSON ListedAccess where
  parseJSON :: Value -> Parser ListedAccess
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ListedAccess"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe HomeDirectoryType
-> Maybe Text
-> ListedAccess
ListedAccess'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ExternalId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"HomeDirectory")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"HomeDirectoryType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Role")
      )

instance Prelude.Hashable ListedAccess where
  hashWithSalt :: Int -> ListedAccess -> Int
hashWithSalt Int
_salt ListedAccess' {Maybe Text
Maybe HomeDirectoryType
role' :: Maybe Text
homeDirectoryType :: Maybe HomeDirectoryType
homeDirectory :: Maybe Text
externalId :: Maybe Text
$sel:role':ListedAccess' :: ListedAccess -> Maybe Text
$sel:homeDirectoryType:ListedAccess' :: ListedAccess -> Maybe HomeDirectoryType
$sel:homeDirectory:ListedAccess' :: ListedAccess -> Maybe Text
$sel:externalId:ListedAccess' :: ListedAccess -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
externalId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
homeDirectory
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HomeDirectoryType
homeDirectoryType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
role'

instance Prelude.NFData ListedAccess where
  rnf :: ListedAccess -> ()
rnf ListedAccess' {Maybe Text
Maybe HomeDirectoryType
role' :: Maybe Text
homeDirectoryType :: Maybe HomeDirectoryType
homeDirectory :: Maybe Text
externalId :: Maybe Text
$sel:role':ListedAccess' :: ListedAccess -> Maybe Text
$sel:homeDirectoryType:ListedAccess' :: ListedAccess -> Maybe HomeDirectoryType
$sel:homeDirectory:ListedAccess' :: ListedAccess -> Maybe Text
$sel:externalId:ListedAccess' :: ListedAccess -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
externalId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
homeDirectory
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HomeDirectoryType
homeDirectoryType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
role'