{-# 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.ListHostKeys
-- 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 a list of host keys for the server that\'s specified by the
-- @ServerId@ parameter.
module Amazonka.Transfer.ListHostKeys
  ( -- * Creating a Request
    ListHostKeys (..),
    newListHostKeys,

    -- * Request Lenses
    listHostKeys_maxResults,
    listHostKeys_nextToken,
    listHostKeys_serverId,

    -- * Destructuring the Response
    ListHostKeysResponse (..),
    newListHostKeysResponse,

    -- * Response Lenses
    listHostKeysResponse_nextToken,
    listHostKeysResponse_httpStatus,
    listHostKeysResponse_serverId,
    listHostKeysResponse_hostKeys,
  )
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:/ 'newListHostKeys' smart constructor.
data ListHostKeys = ListHostKeys'
  { -- | The maximum number of host keys to return.
    ListHostKeys -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | When there are additional results that were not returned, a @NextToken@
    -- parameter is returned. You can use that value for a subsequent call to
    -- @ListHostKeys@ to continue listing results.
    ListHostKeys -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the server that contains the host keys that you want
    -- to view.
    ListHostKeys -> Text
serverId :: Prelude.Text
  }
  deriving (ListHostKeys -> ListHostKeys -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListHostKeys -> ListHostKeys -> Bool
$c/= :: ListHostKeys -> ListHostKeys -> Bool
== :: ListHostKeys -> ListHostKeys -> Bool
$c== :: ListHostKeys -> ListHostKeys -> Bool
Prelude.Eq, ReadPrec [ListHostKeys]
ReadPrec ListHostKeys
Int -> ReadS ListHostKeys
ReadS [ListHostKeys]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListHostKeys]
$creadListPrec :: ReadPrec [ListHostKeys]
readPrec :: ReadPrec ListHostKeys
$creadPrec :: ReadPrec ListHostKeys
readList :: ReadS [ListHostKeys]
$creadList :: ReadS [ListHostKeys]
readsPrec :: Int -> ReadS ListHostKeys
$creadsPrec :: Int -> ReadS ListHostKeys
Prelude.Read, Int -> ListHostKeys -> ShowS
[ListHostKeys] -> ShowS
ListHostKeys -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListHostKeys] -> ShowS
$cshowList :: [ListHostKeys] -> ShowS
show :: ListHostKeys -> String
$cshow :: ListHostKeys -> String
showsPrec :: Int -> ListHostKeys -> ShowS
$cshowsPrec :: Int -> ListHostKeys -> ShowS
Prelude.Show, forall x. Rep ListHostKeys x -> ListHostKeys
forall x. ListHostKeys -> Rep ListHostKeys x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListHostKeys x -> ListHostKeys
$cfrom :: forall x. ListHostKeys -> Rep ListHostKeys x
Prelude.Generic)

-- |
-- Create a value of 'ListHostKeys' 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', 'listHostKeys_maxResults' - The maximum number of host keys to return.
--
-- 'nextToken', 'listHostKeys_nextToken' - When there are additional results that were not returned, a @NextToken@
-- parameter is returned. You can use that value for a subsequent call to
-- @ListHostKeys@ to continue listing results.
--
-- 'serverId', 'listHostKeys_serverId' - The identifier of the server that contains the host keys that you want
-- to view.
newListHostKeys ::
  -- | 'serverId'
  Prelude.Text ->
  ListHostKeys
newListHostKeys :: Text -> ListHostKeys
newListHostKeys Text
pServerId_ =
  ListHostKeys'
    { $sel:maxResults:ListHostKeys' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListHostKeys' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:serverId:ListHostKeys' :: Text
serverId = Text
pServerId_
    }

-- | The maximum number of host keys to return.
listHostKeys_maxResults :: Lens.Lens' ListHostKeys (Prelude.Maybe Prelude.Natural)
listHostKeys_maxResults :: Lens' ListHostKeys (Maybe Natural)
listHostKeys_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHostKeys' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListHostKeys' :: ListHostKeys -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListHostKeys
s@ListHostKeys' {} Maybe Natural
a -> ListHostKeys
s {$sel:maxResults:ListHostKeys' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListHostKeys)

-- | When there are additional results that were not returned, a @NextToken@
-- parameter is returned. You can use that value for a subsequent call to
-- @ListHostKeys@ to continue listing results.
listHostKeys_nextToken :: Lens.Lens' ListHostKeys (Prelude.Maybe Prelude.Text)
listHostKeys_nextToken :: Lens' ListHostKeys (Maybe Text)
listHostKeys_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHostKeys' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListHostKeys' :: ListHostKeys -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListHostKeys
s@ListHostKeys' {} Maybe Text
a -> ListHostKeys
s {$sel:nextToken:ListHostKeys' :: Maybe Text
nextToken = Maybe Text
a} :: ListHostKeys)

-- | The identifier of the server that contains the host keys that you want
-- to view.
listHostKeys_serverId :: Lens.Lens' ListHostKeys Prelude.Text
listHostKeys_serverId :: Lens' ListHostKeys Text
listHostKeys_serverId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHostKeys' {Text
serverId :: Text
$sel:serverId:ListHostKeys' :: ListHostKeys -> Text
serverId} -> Text
serverId) (\s :: ListHostKeys
s@ListHostKeys' {} Text
a -> ListHostKeys
s {$sel:serverId:ListHostKeys' :: Text
serverId = Text
a} :: ListHostKeys)

instance Core.AWSRequest ListHostKeys where
  type AWSResponse ListHostKeys = ListHostKeysResponse
  request :: (Service -> Service) -> ListHostKeys -> Request ListHostKeys
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 ListHostKeys
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListHostKeys)))
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
-> Int -> Text -> [ListedHostKey] -> ListHostKeysResponse
ListHostKeysResponse'
            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
"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))
            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 (Maybe a)
Data..?> Key
"HostKeys" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ListHostKeys where
  hashWithSalt :: Int -> ListHostKeys -> Int
hashWithSalt Int
_salt ListHostKeys' {Maybe Natural
Maybe Text
Text
serverId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:serverId:ListHostKeys' :: ListHostKeys -> Text
$sel:nextToken:ListHostKeys' :: ListHostKeys -> Maybe Text
$sel:maxResults:ListHostKeys' :: ListHostKeys -> 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
serverId

instance Prelude.NFData ListHostKeys where
  rnf :: ListHostKeys -> ()
rnf ListHostKeys' {Maybe Natural
Maybe Text
Text
serverId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:serverId:ListHostKeys' :: ListHostKeys -> Text
$sel:nextToken:ListHostKeys' :: ListHostKeys -> Maybe Text
$sel:maxResults:ListHostKeys' :: ListHostKeys -> 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
serverId

instance Data.ToHeaders ListHostKeys where
  toHeaders :: ListHostKeys -> 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.ListHostKeys" ::
                          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 ListHostKeys where
  toJSON :: ListHostKeys -> Value
toJSON ListHostKeys' {Maybe Natural
Maybe Text
Text
serverId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:serverId:ListHostKeys' :: ListHostKeys -> Text
$sel:nextToken:ListHostKeys' :: ListHostKeys -> Maybe Text
$sel:maxResults:ListHostKeys' :: ListHostKeys -> 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
"ServerId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serverId)
          ]
      )

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

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

-- | /See:/ 'newListHostKeysResponse' smart constructor.
data ListHostKeysResponse = ListHostKeysResponse'
  { -- | Returns a token that you can use to call @ListHostKeys@ again and
    -- receive additional results, if there are any.
    ListHostKeysResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListHostKeysResponse -> Int
httpStatus :: Prelude.Int,
    -- | Returns the server identifier that contains the listed host keys.
    ListHostKeysResponse -> Text
serverId :: Prelude.Text,
    -- | Returns an array, where each item contains the details of a host key.
    ListHostKeysResponse -> [ListedHostKey]
hostKeys :: [ListedHostKey]
  }
  deriving (ListHostKeysResponse -> ListHostKeysResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListHostKeysResponse -> ListHostKeysResponse -> Bool
$c/= :: ListHostKeysResponse -> ListHostKeysResponse -> Bool
== :: ListHostKeysResponse -> ListHostKeysResponse -> Bool
$c== :: ListHostKeysResponse -> ListHostKeysResponse -> Bool
Prelude.Eq, ReadPrec [ListHostKeysResponse]
ReadPrec ListHostKeysResponse
Int -> ReadS ListHostKeysResponse
ReadS [ListHostKeysResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListHostKeysResponse]
$creadListPrec :: ReadPrec [ListHostKeysResponse]
readPrec :: ReadPrec ListHostKeysResponse
$creadPrec :: ReadPrec ListHostKeysResponse
readList :: ReadS [ListHostKeysResponse]
$creadList :: ReadS [ListHostKeysResponse]
readsPrec :: Int -> ReadS ListHostKeysResponse
$creadsPrec :: Int -> ReadS ListHostKeysResponse
Prelude.Read, Int -> ListHostKeysResponse -> ShowS
[ListHostKeysResponse] -> ShowS
ListHostKeysResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListHostKeysResponse] -> ShowS
$cshowList :: [ListHostKeysResponse] -> ShowS
show :: ListHostKeysResponse -> String
$cshow :: ListHostKeysResponse -> String
showsPrec :: Int -> ListHostKeysResponse -> ShowS
$cshowsPrec :: Int -> ListHostKeysResponse -> ShowS
Prelude.Show, forall x. Rep ListHostKeysResponse x -> ListHostKeysResponse
forall x. ListHostKeysResponse -> Rep ListHostKeysResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListHostKeysResponse x -> ListHostKeysResponse
$cfrom :: forall x. ListHostKeysResponse -> Rep ListHostKeysResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListHostKeysResponse' 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:
--
-- 'nextToken', 'listHostKeysResponse_nextToken' - Returns a token that you can use to call @ListHostKeys@ again and
-- receive additional results, if there are any.
--
-- 'httpStatus', 'listHostKeysResponse_httpStatus' - The response's http status code.
--
-- 'serverId', 'listHostKeysResponse_serverId' - Returns the server identifier that contains the listed host keys.
--
-- 'hostKeys', 'listHostKeysResponse_hostKeys' - Returns an array, where each item contains the details of a host key.
newListHostKeysResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'serverId'
  Prelude.Text ->
  ListHostKeysResponse
newListHostKeysResponse :: Int -> Text -> ListHostKeysResponse
newListHostKeysResponse Int
pHttpStatus_ Text
pServerId_ =
  ListHostKeysResponse'
    { $sel:nextToken:ListHostKeysResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListHostKeysResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:serverId:ListHostKeysResponse' :: Text
serverId = Text
pServerId_,
      $sel:hostKeys:ListHostKeysResponse' :: [ListedHostKey]
hostKeys = forall a. Monoid a => a
Prelude.mempty
    }

-- | Returns a token that you can use to call @ListHostKeys@ again and
-- receive additional results, if there are any.
listHostKeysResponse_nextToken :: Lens.Lens' ListHostKeysResponse (Prelude.Maybe Prelude.Text)
listHostKeysResponse_nextToken :: Lens' ListHostKeysResponse (Maybe Text)
listHostKeysResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHostKeysResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListHostKeysResponse' :: ListHostKeysResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListHostKeysResponse
s@ListHostKeysResponse' {} Maybe Text
a -> ListHostKeysResponse
s {$sel:nextToken:ListHostKeysResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListHostKeysResponse)

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

-- | Returns the server identifier that contains the listed host keys.
listHostKeysResponse_serverId :: Lens.Lens' ListHostKeysResponse Prelude.Text
listHostKeysResponse_serverId :: Lens' ListHostKeysResponse Text
listHostKeysResponse_serverId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHostKeysResponse' {Text
serverId :: Text
$sel:serverId:ListHostKeysResponse' :: ListHostKeysResponse -> Text
serverId} -> Text
serverId) (\s :: ListHostKeysResponse
s@ListHostKeysResponse' {} Text
a -> ListHostKeysResponse
s {$sel:serverId:ListHostKeysResponse' :: Text
serverId = Text
a} :: ListHostKeysResponse)

-- | Returns an array, where each item contains the details of a host key.
listHostKeysResponse_hostKeys :: Lens.Lens' ListHostKeysResponse [ListedHostKey]
listHostKeysResponse_hostKeys :: Lens' ListHostKeysResponse [ListedHostKey]
listHostKeysResponse_hostKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListHostKeysResponse' {[ListedHostKey]
hostKeys :: [ListedHostKey]
$sel:hostKeys:ListHostKeysResponse' :: ListHostKeysResponse -> [ListedHostKey]
hostKeys} -> [ListedHostKey]
hostKeys) (\s :: ListHostKeysResponse
s@ListHostKeysResponse' {} [ListedHostKey]
a -> ListHostKeysResponse
s {$sel:hostKeys:ListHostKeysResponse' :: [ListedHostKey]
hostKeys = [ListedHostKey]
a} :: ListHostKeysResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Prelude.NFData ListHostKeysResponse where
  rnf :: ListHostKeysResponse -> ()
rnf ListHostKeysResponse' {Int
[ListedHostKey]
Maybe Text
Text
hostKeys :: [ListedHostKey]
serverId :: Text
httpStatus :: Int
nextToken :: Maybe Text
$sel:hostKeys:ListHostKeysResponse' :: ListHostKeysResponse -> [ListedHostKey]
$sel:serverId:ListHostKeysResponse' :: ListHostKeysResponse -> Text
$sel:httpStatus:ListHostKeysResponse' :: ListHostKeysResponse -> Int
$sel:nextToken:ListHostKeysResponse' :: ListHostKeysResponse -> Maybe Text
..} =
    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
      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 [ListedHostKey]
hostKeys