{-# 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.CloudHSM.ListAvailableZones
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This is documentation for __AWS CloudHSM Classic__. For more
-- information, see
-- <http://aws.amazon.com/cloudhsm/faqs-classic/ AWS CloudHSM Classic FAQs>,
-- the
-- <https://docs.aws.amazon.com/cloudhsm/classic/userguide/ AWS CloudHSM Classic User Guide>,
-- and the
-- <https://docs.aws.amazon.com/cloudhsm/classic/APIReference/ AWS CloudHSM Classic API Reference>.
--
-- __For information about the current version of AWS CloudHSM__, see
-- <http://aws.amazon.com/cloudhsm/ AWS CloudHSM>, the
-- <https://docs.aws.amazon.com/cloudhsm/latest/userguide/ AWS CloudHSM User Guide>,
-- and the
-- <https://docs.aws.amazon.com/cloudhsm/latest/APIReference/ AWS CloudHSM API Reference>.
--
-- Lists the Availability Zones that have available AWS CloudHSM capacity.
module Amazonka.CloudHSM.ListAvailableZones
  ( -- * Creating a Request
    ListAvailableZones (..),
    newListAvailableZones,

    -- * Destructuring the Response
    ListAvailableZonesResponse (..),
    newListAvailableZonesResponse,

    -- * Response Lenses
    listAvailableZonesResponse_aZList,
    listAvailableZonesResponse_httpStatus,
  )
where

import Amazonka.CloudHSM.Types
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

-- | Contains the inputs for the ListAvailableZones action.
--
-- /See:/ 'newListAvailableZones' smart constructor.
data ListAvailableZones = ListAvailableZones'
  {
  }
  deriving (ListAvailableZones -> ListAvailableZones -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAvailableZones -> ListAvailableZones -> Bool
$c/= :: ListAvailableZones -> ListAvailableZones -> Bool
== :: ListAvailableZones -> ListAvailableZones -> Bool
$c== :: ListAvailableZones -> ListAvailableZones -> Bool
Prelude.Eq, ReadPrec [ListAvailableZones]
ReadPrec ListAvailableZones
Int -> ReadS ListAvailableZones
ReadS [ListAvailableZones]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAvailableZones]
$creadListPrec :: ReadPrec [ListAvailableZones]
readPrec :: ReadPrec ListAvailableZones
$creadPrec :: ReadPrec ListAvailableZones
readList :: ReadS [ListAvailableZones]
$creadList :: ReadS [ListAvailableZones]
readsPrec :: Int -> ReadS ListAvailableZones
$creadsPrec :: Int -> ReadS ListAvailableZones
Prelude.Read, Int -> ListAvailableZones -> ShowS
[ListAvailableZones] -> ShowS
ListAvailableZones -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAvailableZones] -> ShowS
$cshowList :: [ListAvailableZones] -> ShowS
show :: ListAvailableZones -> String
$cshow :: ListAvailableZones -> String
showsPrec :: Int -> ListAvailableZones -> ShowS
$cshowsPrec :: Int -> ListAvailableZones -> ShowS
Prelude.Show, forall x. Rep ListAvailableZones x -> ListAvailableZones
forall x. ListAvailableZones -> Rep ListAvailableZones x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAvailableZones x -> ListAvailableZones
$cfrom :: forall x. ListAvailableZones -> Rep ListAvailableZones x
Prelude.Generic)

-- |
-- Create a value of 'ListAvailableZones' 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.
newListAvailableZones ::
  ListAvailableZones
newListAvailableZones :: ListAvailableZones
newListAvailableZones = ListAvailableZones
ListAvailableZones'

instance Core.AWSRequest ListAvailableZones where
  type
    AWSResponse ListAvailableZones =
      ListAvailableZonesResponse
  request :: (Service -> Service)
-> ListAvailableZones -> Request ListAvailableZones
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 ListAvailableZones
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListAvailableZones)))
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 -> ListAvailableZonesResponse
ListAvailableZonesResponse'
            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
"AZList" 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 ListAvailableZones where
  hashWithSalt :: Int -> ListAvailableZones -> Int
hashWithSalt Int
_salt ListAvailableZones
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

instance Prelude.NFData ListAvailableZones where
  rnf :: ListAvailableZones -> ()
rnf ListAvailableZones
_ = ()

instance Data.ToHeaders ListAvailableZones where
  toHeaders :: ListAvailableZones -> 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
"CloudHsmFrontendService.ListAvailableZones" ::
                          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 ListAvailableZones where
  toJSON :: ListAvailableZones -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

-- | /See:/ 'newListAvailableZonesResponse' smart constructor.
data ListAvailableZonesResponse = ListAvailableZonesResponse'
  { -- | The list of Availability Zones that have available AWS CloudHSM
    -- capacity.
    ListAvailableZonesResponse -> Maybe [Text]
aZList :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    ListAvailableZonesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListAvailableZonesResponse -> ListAvailableZonesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAvailableZonesResponse -> ListAvailableZonesResponse -> Bool
$c/= :: ListAvailableZonesResponse -> ListAvailableZonesResponse -> Bool
== :: ListAvailableZonesResponse -> ListAvailableZonesResponse -> Bool
$c== :: ListAvailableZonesResponse -> ListAvailableZonesResponse -> Bool
Prelude.Eq, ReadPrec [ListAvailableZonesResponse]
ReadPrec ListAvailableZonesResponse
Int -> ReadS ListAvailableZonesResponse
ReadS [ListAvailableZonesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAvailableZonesResponse]
$creadListPrec :: ReadPrec [ListAvailableZonesResponse]
readPrec :: ReadPrec ListAvailableZonesResponse
$creadPrec :: ReadPrec ListAvailableZonesResponse
readList :: ReadS [ListAvailableZonesResponse]
$creadList :: ReadS [ListAvailableZonesResponse]
readsPrec :: Int -> ReadS ListAvailableZonesResponse
$creadsPrec :: Int -> ReadS ListAvailableZonesResponse
Prelude.Read, Int -> ListAvailableZonesResponse -> ShowS
[ListAvailableZonesResponse] -> ShowS
ListAvailableZonesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAvailableZonesResponse] -> ShowS
$cshowList :: [ListAvailableZonesResponse] -> ShowS
show :: ListAvailableZonesResponse -> String
$cshow :: ListAvailableZonesResponse -> String
showsPrec :: Int -> ListAvailableZonesResponse -> ShowS
$cshowsPrec :: Int -> ListAvailableZonesResponse -> ShowS
Prelude.Show, forall x.
Rep ListAvailableZonesResponse x -> ListAvailableZonesResponse
forall x.
ListAvailableZonesResponse -> Rep ListAvailableZonesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAvailableZonesResponse x -> ListAvailableZonesResponse
$cfrom :: forall x.
ListAvailableZonesResponse -> Rep ListAvailableZonesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAvailableZonesResponse' 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:
--
-- 'aZList', 'listAvailableZonesResponse_aZList' - The list of Availability Zones that have available AWS CloudHSM
-- capacity.
--
-- 'httpStatus', 'listAvailableZonesResponse_httpStatus' - The response's http status code.
newListAvailableZonesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAvailableZonesResponse
newListAvailableZonesResponse :: Int -> ListAvailableZonesResponse
newListAvailableZonesResponse Int
pHttpStatus_ =
  ListAvailableZonesResponse'
    { $sel:aZList:ListAvailableZonesResponse' :: Maybe [Text]
aZList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAvailableZonesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of Availability Zones that have available AWS CloudHSM
-- capacity.
listAvailableZonesResponse_aZList :: Lens.Lens' ListAvailableZonesResponse (Prelude.Maybe [Prelude.Text])
listAvailableZonesResponse_aZList :: Lens' ListAvailableZonesResponse (Maybe [Text])
listAvailableZonesResponse_aZList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAvailableZonesResponse' {Maybe [Text]
aZList :: Maybe [Text]
$sel:aZList:ListAvailableZonesResponse' :: ListAvailableZonesResponse -> Maybe [Text]
aZList} -> Maybe [Text]
aZList) (\s :: ListAvailableZonesResponse
s@ListAvailableZonesResponse' {} Maybe [Text]
a -> ListAvailableZonesResponse
s {$sel:aZList:ListAvailableZonesResponse' :: Maybe [Text]
aZList = Maybe [Text]
a} :: ListAvailableZonesResponse) 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.
listAvailableZonesResponse_httpStatus :: Lens.Lens' ListAvailableZonesResponse Prelude.Int
listAvailableZonesResponse_httpStatus :: Lens' ListAvailableZonesResponse Int
listAvailableZonesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAvailableZonesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListAvailableZonesResponse' :: ListAvailableZonesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListAvailableZonesResponse
s@ListAvailableZonesResponse' {} Int
a -> ListAvailableZonesResponse
s {$sel:httpStatus:ListAvailableZonesResponse' :: Int
httpStatus = Int
a} :: ListAvailableZonesResponse)

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