{-# 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.Route53.GetHostedZoneCount
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the number of hosted zones that are associated with the
-- current Amazon Web Services account.
module Amazonka.Route53.GetHostedZoneCount
  ( -- * Creating a Request
    GetHostedZoneCount (..),
    newGetHostedZoneCount,

    -- * Destructuring the Response
    GetHostedZoneCountResponse (..),
    newGetHostedZoneCountResponse,

    -- * Response Lenses
    getHostedZoneCountResponse_httpStatus,
    getHostedZoneCountResponse_hostedZoneCount,
  )
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.Route53.Types

-- | A request to retrieve a count of all the hosted zones that are
-- associated with the current Amazon Web Services account.
--
-- /See:/ 'newGetHostedZoneCount' smart constructor.
data GetHostedZoneCount = GetHostedZoneCount'
  {
  }
  deriving (GetHostedZoneCount -> GetHostedZoneCount -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetHostedZoneCount -> GetHostedZoneCount -> Bool
$c/= :: GetHostedZoneCount -> GetHostedZoneCount -> Bool
== :: GetHostedZoneCount -> GetHostedZoneCount -> Bool
$c== :: GetHostedZoneCount -> GetHostedZoneCount -> Bool
Prelude.Eq, ReadPrec [GetHostedZoneCount]
ReadPrec GetHostedZoneCount
Int -> ReadS GetHostedZoneCount
ReadS [GetHostedZoneCount]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetHostedZoneCount]
$creadListPrec :: ReadPrec [GetHostedZoneCount]
readPrec :: ReadPrec GetHostedZoneCount
$creadPrec :: ReadPrec GetHostedZoneCount
readList :: ReadS [GetHostedZoneCount]
$creadList :: ReadS [GetHostedZoneCount]
readsPrec :: Int -> ReadS GetHostedZoneCount
$creadsPrec :: Int -> ReadS GetHostedZoneCount
Prelude.Read, Int -> GetHostedZoneCount -> ShowS
[GetHostedZoneCount] -> ShowS
GetHostedZoneCount -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetHostedZoneCount] -> ShowS
$cshowList :: [GetHostedZoneCount] -> ShowS
show :: GetHostedZoneCount -> String
$cshow :: GetHostedZoneCount -> String
showsPrec :: Int -> GetHostedZoneCount -> ShowS
$cshowsPrec :: Int -> GetHostedZoneCount -> ShowS
Prelude.Show, forall x. Rep GetHostedZoneCount x -> GetHostedZoneCount
forall x. GetHostedZoneCount -> Rep GetHostedZoneCount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetHostedZoneCount x -> GetHostedZoneCount
$cfrom :: forall x. GetHostedZoneCount -> Rep GetHostedZoneCount x
Prelude.Generic)

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

instance Core.AWSRequest GetHostedZoneCount where
  type
    AWSResponse GetHostedZoneCount =
      GetHostedZoneCountResponse
  request :: (Service -> Service)
-> GetHostedZoneCount -> Request GetHostedZoneCount
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetHostedZoneCount
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetHostedZoneCount)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> Integer -> GetHostedZoneCountResponse
GetHostedZoneCountResponse'
            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.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"HostedZoneCount")
      )

instance Prelude.Hashable GetHostedZoneCount where
  hashWithSalt :: Int -> GetHostedZoneCount -> Int
hashWithSalt Int
_salt GetHostedZoneCount
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

instance Data.ToHeaders GetHostedZoneCount where
  toHeaders :: GetHostedZoneCount -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath GetHostedZoneCount where
  toPath :: GetHostedZoneCount -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2013-04-01/hostedzonecount"

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

-- | A complex type that contains the response to a @GetHostedZoneCount@
-- request.
--
-- /See:/ 'newGetHostedZoneCountResponse' smart constructor.
data GetHostedZoneCountResponse = GetHostedZoneCountResponse'
  { -- | The response's http status code.
    GetHostedZoneCountResponse -> Int
httpStatus :: Prelude.Int,
    -- | The total number of public and private hosted zones that are associated
    -- with the current Amazon Web Services account.
    GetHostedZoneCountResponse -> Integer
hostedZoneCount :: Prelude.Integer
  }
  deriving (GetHostedZoneCountResponse -> GetHostedZoneCountResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetHostedZoneCountResponse -> GetHostedZoneCountResponse -> Bool
$c/= :: GetHostedZoneCountResponse -> GetHostedZoneCountResponse -> Bool
== :: GetHostedZoneCountResponse -> GetHostedZoneCountResponse -> Bool
$c== :: GetHostedZoneCountResponse -> GetHostedZoneCountResponse -> Bool
Prelude.Eq, ReadPrec [GetHostedZoneCountResponse]
ReadPrec GetHostedZoneCountResponse
Int -> ReadS GetHostedZoneCountResponse
ReadS [GetHostedZoneCountResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetHostedZoneCountResponse]
$creadListPrec :: ReadPrec [GetHostedZoneCountResponse]
readPrec :: ReadPrec GetHostedZoneCountResponse
$creadPrec :: ReadPrec GetHostedZoneCountResponse
readList :: ReadS [GetHostedZoneCountResponse]
$creadList :: ReadS [GetHostedZoneCountResponse]
readsPrec :: Int -> ReadS GetHostedZoneCountResponse
$creadsPrec :: Int -> ReadS GetHostedZoneCountResponse
Prelude.Read, Int -> GetHostedZoneCountResponse -> ShowS
[GetHostedZoneCountResponse] -> ShowS
GetHostedZoneCountResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetHostedZoneCountResponse] -> ShowS
$cshowList :: [GetHostedZoneCountResponse] -> ShowS
show :: GetHostedZoneCountResponse -> String
$cshow :: GetHostedZoneCountResponse -> String
showsPrec :: Int -> GetHostedZoneCountResponse -> ShowS
$cshowsPrec :: Int -> GetHostedZoneCountResponse -> ShowS
Prelude.Show, forall x.
Rep GetHostedZoneCountResponse x -> GetHostedZoneCountResponse
forall x.
GetHostedZoneCountResponse -> Rep GetHostedZoneCountResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetHostedZoneCountResponse x -> GetHostedZoneCountResponse
$cfrom :: forall x.
GetHostedZoneCountResponse -> Rep GetHostedZoneCountResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetHostedZoneCountResponse' 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', 'getHostedZoneCountResponse_httpStatus' - The response's http status code.
--
-- 'hostedZoneCount', 'getHostedZoneCountResponse_hostedZoneCount' - The total number of public and private hosted zones that are associated
-- with the current Amazon Web Services account.
newGetHostedZoneCountResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'hostedZoneCount'
  Prelude.Integer ->
  GetHostedZoneCountResponse
newGetHostedZoneCountResponse :: Int -> Integer -> GetHostedZoneCountResponse
newGetHostedZoneCountResponse
  Int
pHttpStatus_
  Integer
pHostedZoneCount_ =
    GetHostedZoneCountResponse'
      { $sel:httpStatus:GetHostedZoneCountResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:hostedZoneCount:GetHostedZoneCountResponse' :: Integer
hostedZoneCount = Integer
pHostedZoneCount_
      }

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

-- | The total number of public and private hosted zones that are associated
-- with the current Amazon Web Services account.
getHostedZoneCountResponse_hostedZoneCount :: Lens.Lens' GetHostedZoneCountResponse Prelude.Integer
getHostedZoneCountResponse_hostedZoneCount :: Lens' GetHostedZoneCountResponse Integer
getHostedZoneCountResponse_hostedZoneCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetHostedZoneCountResponse' {Integer
hostedZoneCount :: Integer
$sel:hostedZoneCount:GetHostedZoneCountResponse' :: GetHostedZoneCountResponse -> Integer
hostedZoneCount} -> Integer
hostedZoneCount) (\s :: GetHostedZoneCountResponse
s@GetHostedZoneCountResponse' {} Integer
a -> GetHostedZoneCountResponse
s {$sel:hostedZoneCount:GetHostedZoneCountResponse' :: Integer
hostedZoneCount = Integer
a} :: GetHostedZoneCountResponse)

instance Prelude.NFData GetHostedZoneCountResponse where
  rnf :: GetHostedZoneCountResponse -> ()
rnf GetHostedZoneCountResponse' {Int
Integer
hostedZoneCount :: Integer
httpStatus :: Int
$sel:hostedZoneCount:GetHostedZoneCountResponse' :: GetHostedZoneCountResponse -> Integer
$sel:httpStatus:GetHostedZoneCountResponse' :: GetHostedZoneCountResponse -> 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 Integer
hostedZoneCount