{-# 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.Lightsail.GetBucketAccessKeys
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the existing access key IDs for the specified Amazon Lightsail
-- bucket.
--
-- This action does not return the secret access key value of an access
-- key. You can get a secret access key only when you create it from the
-- response of the
-- <https://docs.aws.amazon.com/lightsail/2016-11-28/api-reference/API_CreateBucketAccessKey.html CreateBucketAccessKey>
-- action. If you lose the secret access key, you must create a new access
-- key.
module Amazonka.Lightsail.GetBucketAccessKeys
  ( -- * Creating a Request
    GetBucketAccessKeys (..),
    newGetBucketAccessKeys,

    -- * Request Lenses
    getBucketAccessKeys_bucketName,

    -- * Destructuring the Response
    GetBucketAccessKeysResponse (..),
    newGetBucketAccessKeysResponse,

    -- * Response Lenses
    getBucketAccessKeysResponse_accessKeys,
    getBucketAccessKeysResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetBucketAccessKeys' smart constructor.
data GetBucketAccessKeys = GetBucketAccessKeys'
  { -- | The name of the bucket for which to return access keys.
    GetBucketAccessKeys -> Text
bucketName :: Prelude.Text
  }
  deriving (GetBucketAccessKeys -> GetBucketAccessKeys -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBucketAccessKeys -> GetBucketAccessKeys -> Bool
$c/= :: GetBucketAccessKeys -> GetBucketAccessKeys -> Bool
== :: GetBucketAccessKeys -> GetBucketAccessKeys -> Bool
$c== :: GetBucketAccessKeys -> GetBucketAccessKeys -> Bool
Prelude.Eq, ReadPrec [GetBucketAccessKeys]
ReadPrec GetBucketAccessKeys
Int -> ReadS GetBucketAccessKeys
ReadS [GetBucketAccessKeys]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBucketAccessKeys]
$creadListPrec :: ReadPrec [GetBucketAccessKeys]
readPrec :: ReadPrec GetBucketAccessKeys
$creadPrec :: ReadPrec GetBucketAccessKeys
readList :: ReadS [GetBucketAccessKeys]
$creadList :: ReadS [GetBucketAccessKeys]
readsPrec :: Int -> ReadS GetBucketAccessKeys
$creadsPrec :: Int -> ReadS GetBucketAccessKeys
Prelude.Read, Int -> GetBucketAccessKeys -> ShowS
[GetBucketAccessKeys] -> ShowS
GetBucketAccessKeys -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBucketAccessKeys] -> ShowS
$cshowList :: [GetBucketAccessKeys] -> ShowS
show :: GetBucketAccessKeys -> String
$cshow :: GetBucketAccessKeys -> String
showsPrec :: Int -> GetBucketAccessKeys -> ShowS
$cshowsPrec :: Int -> GetBucketAccessKeys -> ShowS
Prelude.Show, forall x. Rep GetBucketAccessKeys x -> GetBucketAccessKeys
forall x. GetBucketAccessKeys -> Rep GetBucketAccessKeys x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBucketAccessKeys x -> GetBucketAccessKeys
$cfrom :: forall x. GetBucketAccessKeys -> Rep GetBucketAccessKeys x
Prelude.Generic)

-- |
-- Create a value of 'GetBucketAccessKeys' 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:
--
-- 'bucketName', 'getBucketAccessKeys_bucketName' - The name of the bucket for which to return access keys.
newGetBucketAccessKeys ::
  -- | 'bucketName'
  Prelude.Text ->
  GetBucketAccessKeys
newGetBucketAccessKeys :: Text -> GetBucketAccessKeys
newGetBucketAccessKeys Text
pBucketName_ =
  GetBucketAccessKeys' {$sel:bucketName:GetBucketAccessKeys' :: Text
bucketName = Text
pBucketName_}

-- | The name of the bucket for which to return access keys.
getBucketAccessKeys_bucketName :: Lens.Lens' GetBucketAccessKeys Prelude.Text
getBucketAccessKeys_bucketName :: Lens' GetBucketAccessKeys Text
getBucketAccessKeys_bucketName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketAccessKeys' {Text
bucketName :: Text
$sel:bucketName:GetBucketAccessKeys' :: GetBucketAccessKeys -> Text
bucketName} -> Text
bucketName) (\s :: GetBucketAccessKeys
s@GetBucketAccessKeys' {} Text
a -> GetBucketAccessKeys
s {$sel:bucketName:GetBucketAccessKeys' :: Text
bucketName = Text
a} :: GetBucketAccessKeys)

instance Core.AWSRequest GetBucketAccessKeys where
  type
    AWSResponse GetBucketAccessKeys =
      GetBucketAccessKeysResponse
  request :: (Service -> Service)
-> GetBucketAccessKeys -> Request GetBucketAccessKeys
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 GetBucketAccessKeys
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetBucketAccessKeys)))
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 [AccessKey] -> Int -> GetBucketAccessKeysResponse
GetBucketAccessKeysResponse'
            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
"accessKeys" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

instance Prelude.NFData GetBucketAccessKeys where
  rnf :: GetBucketAccessKeys -> ()
rnf GetBucketAccessKeys' {Text
bucketName :: Text
$sel:bucketName:GetBucketAccessKeys' :: GetBucketAccessKeys -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
bucketName

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

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

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

-- | /See:/ 'newGetBucketAccessKeysResponse' smart constructor.
data GetBucketAccessKeysResponse = GetBucketAccessKeysResponse'
  { -- | An object that describes the access keys for the specified bucket.
    GetBucketAccessKeysResponse -> Maybe [AccessKey]
accessKeys :: Prelude.Maybe [AccessKey],
    -- | The response's http status code.
    GetBucketAccessKeysResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBucketAccessKeysResponse -> GetBucketAccessKeysResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBucketAccessKeysResponse -> GetBucketAccessKeysResponse -> Bool
$c/= :: GetBucketAccessKeysResponse -> GetBucketAccessKeysResponse -> Bool
== :: GetBucketAccessKeysResponse -> GetBucketAccessKeysResponse -> Bool
$c== :: GetBucketAccessKeysResponse -> GetBucketAccessKeysResponse -> Bool
Prelude.Eq, Int -> GetBucketAccessKeysResponse -> ShowS
[GetBucketAccessKeysResponse] -> ShowS
GetBucketAccessKeysResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBucketAccessKeysResponse] -> ShowS
$cshowList :: [GetBucketAccessKeysResponse] -> ShowS
show :: GetBucketAccessKeysResponse -> String
$cshow :: GetBucketAccessKeysResponse -> String
showsPrec :: Int -> GetBucketAccessKeysResponse -> ShowS
$cshowsPrec :: Int -> GetBucketAccessKeysResponse -> ShowS
Prelude.Show, forall x.
Rep GetBucketAccessKeysResponse x -> GetBucketAccessKeysResponse
forall x.
GetBucketAccessKeysResponse -> Rep GetBucketAccessKeysResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBucketAccessKeysResponse x -> GetBucketAccessKeysResponse
$cfrom :: forall x.
GetBucketAccessKeysResponse -> Rep GetBucketAccessKeysResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBucketAccessKeysResponse' 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:
--
-- 'accessKeys', 'getBucketAccessKeysResponse_accessKeys' - An object that describes the access keys for the specified bucket.
--
-- 'httpStatus', 'getBucketAccessKeysResponse_httpStatus' - The response's http status code.
newGetBucketAccessKeysResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBucketAccessKeysResponse
newGetBucketAccessKeysResponse :: Int -> GetBucketAccessKeysResponse
newGetBucketAccessKeysResponse Int
pHttpStatus_ =
  GetBucketAccessKeysResponse'
    { $sel:accessKeys:GetBucketAccessKeysResponse' :: Maybe [AccessKey]
accessKeys =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBucketAccessKeysResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An object that describes the access keys for the specified bucket.
getBucketAccessKeysResponse_accessKeys :: Lens.Lens' GetBucketAccessKeysResponse (Prelude.Maybe [AccessKey])
getBucketAccessKeysResponse_accessKeys :: Lens' GetBucketAccessKeysResponse (Maybe [AccessKey])
getBucketAccessKeysResponse_accessKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketAccessKeysResponse' {Maybe [AccessKey]
accessKeys :: Maybe [AccessKey]
$sel:accessKeys:GetBucketAccessKeysResponse' :: GetBucketAccessKeysResponse -> Maybe [AccessKey]
accessKeys} -> Maybe [AccessKey]
accessKeys) (\s :: GetBucketAccessKeysResponse
s@GetBucketAccessKeysResponse' {} Maybe [AccessKey]
a -> GetBucketAccessKeysResponse
s {$sel:accessKeys:GetBucketAccessKeysResponse' :: Maybe [AccessKey]
accessKeys = Maybe [AccessKey]
a} :: GetBucketAccessKeysResponse) 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 response's http status code.
getBucketAccessKeysResponse_httpStatus :: Lens.Lens' GetBucketAccessKeysResponse Prelude.Int
getBucketAccessKeysResponse_httpStatus :: Lens' GetBucketAccessKeysResponse Int
getBucketAccessKeysResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketAccessKeysResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetBucketAccessKeysResponse' :: GetBucketAccessKeysResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetBucketAccessKeysResponse
s@GetBucketAccessKeysResponse' {} Int
a -> GetBucketAccessKeysResponse
s {$sel:httpStatus:GetBucketAccessKeysResponse' :: Int
httpStatus = Int
a} :: GetBucketAccessKeysResponse)

instance Prelude.NFData GetBucketAccessKeysResponse where
  rnf :: GetBucketAccessKeysResponse -> ()
rnf GetBucketAccessKeysResponse' {Int
Maybe [AccessKey]
httpStatus :: Int
accessKeys :: Maybe [AccessKey]
$sel:httpStatus:GetBucketAccessKeysResponse' :: GetBucketAccessKeysResponse -> Int
$sel:accessKeys:GetBucketAccessKeysResponse' :: GetBucketAccessKeysResponse -> Maybe [AccessKey]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [AccessKey]
accessKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus