{-# 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.EC2.DescribeAggregateIdFormat
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the longer ID format settings for all resource types in a
-- specific Region. This request is useful for performing a quick audit to
-- determine whether a specific Region is fully opted in for longer IDs
-- (17-character IDs).
--
-- This request only returns information about resource types that support
-- longer IDs.
--
-- The following resource types support longer IDs: @bundle@ |
-- @conversion-task@ | @customer-gateway@ | @dhcp-options@ |
-- @elastic-ip-allocation@ | @elastic-ip-association@ | @export-task@ |
-- @flow-log@ | @image@ | @import-task@ | @instance@ | @internet-gateway@ |
-- @network-acl@ | @network-acl-association@ | @network-interface@ |
-- @network-interface-attachment@ | @prefix-list@ | @reservation@ |
-- @route-table@ | @route-table-association@ | @security-group@ |
-- @snapshot@ | @subnet@ | @subnet-cidr-block-association@ | @volume@ |
-- @vpc@ | @vpc-cidr-block-association@ | @vpc-endpoint@ |
-- @vpc-peering-connection@ | @vpn-connection@ | @vpn-gateway@.
module Amazonka.EC2.DescribeAggregateIdFormat
  ( -- * Creating a Request
    DescribeAggregateIdFormat (..),
    newDescribeAggregateIdFormat,

    -- * Request Lenses
    describeAggregateIdFormat_dryRun,

    -- * Destructuring the Response
    DescribeAggregateIdFormatResponse (..),
    newDescribeAggregateIdFormatResponse,

    -- * Response Lenses
    describeAggregateIdFormatResponse_statuses,
    describeAggregateIdFormatResponse_useLongIdsAggregated,
    describeAggregateIdFormatResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeAggregateIdFormat' smart constructor.
data DescribeAggregateIdFormat = DescribeAggregateIdFormat'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    DescribeAggregateIdFormat -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool
  }
  deriving (DescribeAggregateIdFormat -> DescribeAggregateIdFormat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAggregateIdFormat -> DescribeAggregateIdFormat -> Bool
$c/= :: DescribeAggregateIdFormat -> DescribeAggregateIdFormat -> Bool
== :: DescribeAggregateIdFormat -> DescribeAggregateIdFormat -> Bool
$c== :: DescribeAggregateIdFormat -> DescribeAggregateIdFormat -> Bool
Prelude.Eq, ReadPrec [DescribeAggregateIdFormat]
ReadPrec DescribeAggregateIdFormat
Int -> ReadS DescribeAggregateIdFormat
ReadS [DescribeAggregateIdFormat]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAggregateIdFormat]
$creadListPrec :: ReadPrec [DescribeAggregateIdFormat]
readPrec :: ReadPrec DescribeAggregateIdFormat
$creadPrec :: ReadPrec DescribeAggregateIdFormat
readList :: ReadS [DescribeAggregateIdFormat]
$creadList :: ReadS [DescribeAggregateIdFormat]
readsPrec :: Int -> ReadS DescribeAggregateIdFormat
$creadsPrec :: Int -> ReadS DescribeAggregateIdFormat
Prelude.Read, Int -> DescribeAggregateIdFormat -> ShowS
[DescribeAggregateIdFormat] -> ShowS
DescribeAggregateIdFormat -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAggregateIdFormat] -> ShowS
$cshowList :: [DescribeAggregateIdFormat] -> ShowS
show :: DescribeAggregateIdFormat -> String
$cshow :: DescribeAggregateIdFormat -> String
showsPrec :: Int -> DescribeAggregateIdFormat -> ShowS
$cshowsPrec :: Int -> DescribeAggregateIdFormat -> ShowS
Prelude.Show, forall x.
Rep DescribeAggregateIdFormat x -> DescribeAggregateIdFormat
forall x.
DescribeAggregateIdFormat -> Rep DescribeAggregateIdFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAggregateIdFormat x -> DescribeAggregateIdFormat
$cfrom :: forall x.
DescribeAggregateIdFormat -> Rep DescribeAggregateIdFormat x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAggregateIdFormat' 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:
--
-- 'dryRun', 'describeAggregateIdFormat_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
newDescribeAggregateIdFormat ::
  DescribeAggregateIdFormat
newDescribeAggregateIdFormat :: DescribeAggregateIdFormat
newDescribeAggregateIdFormat =
  DescribeAggregateIdFormat'
    { $sel:dryRun:DescribeAggregateIdFormat' :: Maybe Bool
dryRun =
        forall a. Maybe a
Prelude.Nothing
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
describeAggregateIdFormat_dryRun :: Lens.Lens' DescribeAggregateIdFormat (Prelude.Maybe Prelude.Bool)
describeAggregateIdFormat_dryRun :: Lens' DescribeAggregateIdFormat (Maybe Bool)
describeAggregateIdFormat_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAggregateIdFormat' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DescribeAggregateIdFormat' :: DescribeAggregateIdFormat -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DescribeAggregateIdFormat
s@DescribeAggregateIdFormat' {} Maybe Bool
a -> DescribeAggregateIdFormat
s {$sel:dryRun:DescribeAggregateIdFormat' :: Maybe Bool
dryRun = Maybe Bool
a} :: DescribeAggregateIdFormat)

instance Core.AWSRequest DescribeAggregateIdFormat where
  type
    AWSResponse DescribeAggregateIdFormat =
      DescribeAggregateIdFormatResponse
  request :: (Service -> Service)
-> DescribeAggregateIdFormat -> Request DescribeAggregateIdFormat
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeAggregateIdFormat
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeAggregateIdFormat)))
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 ->
          Maybe [IdFormat]
-> Maybe Bool -> Int -> DescribeAggregateIdFormatResponse
DescribeAggregateIdFormatResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"statusSet"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"useLongIdsAggregated")
            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 DescribeAggregateIdFormat where
  hashWithSalt :: Int -> DescribeAggregateIdFormat -> Int
hashWithSalt Int
_salt DescribeAggregateIdFormat' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DescribeAggregateIdFormat' :: DescribeAggregateIdFormat -> Maybe Bool
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun

instance Prelude.NFData DescribeAggregateIdFormat where
  rnf :: DescribeAggregateIdFormat -> ()
rnf DescribeAggregateIdFormat' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DescribeAggregateIdFormat' :: DescribeAggregateIdFormat -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun

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

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

instance Data.ToQuery DescribeAggregateIdFormat where
  toQuery :: DescribeAggregateIdFormat -> QueryString
toQuery DescribeAggregateIdFormat' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DescribeAggregateIdFormat' :: DescribeAggregateIdFormat -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeAggregateIdFormat" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun
      ]

-- | /See:/ 'newDescribeAggregateIdFormatResponse' smart constructor.
data DescribeAggregateIdFormatResponse = DescribeAggregateIdFormatResponse'
  { -- | Information about each resource\'s ID format.
    DescribeAggregateIdFormatResponse -> Maybe [IdFormat]
statuses :: Prelude.Maybe [IdFormat],
    -- | Indicates whether all resource types in the Region are configured to use
    -- longer IDs. This value is only @true@ if all users are configured to use
    -- longer IDs for all resources types in the Region.
    DescribeAggregateIdFormatResponse -> Maybe Bool
useLongIdsAggregated :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    DescribeAggregateIdFormatResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeAggregateIdFormatResponse
-> DescribeAggregateIdFormatResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAggregateIdFormatResponse
-> DescribeAggregateIdFormatResponse -> Bool
$c/= :: DescribeAggregateIdFormatResponse
-> DescribeAggregateIdFormatResponse -> Bool
== :: DescribeAggregateIdFormatResponse
-> DescribeAggregateIdFormatResponse -> Bool
$c== :: DescribeAggregateIdFormatResponse
-> DescribeAggregateIdFormatResponse -> Bool
Prelude.Eq, ReadPrec [DescribeAggregateIdFormatResponse]
ReadPrec DescribeAggregateIdFormatResponse
Int -> ReadS DescribeAggregateIdFormatResponse
ReadS [DescribeAggregateIdFormatResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAggregateIdFormatResponse]
$creadListPrec :: ReadPrec [DescribeAggregateIdFormatResponse]
readPrec :: ReadPrec DescribeAggregateIdFormatResponse
$creadPrec :: ReadPrec DescribeAggregateIdFormatResponse
readList :: ReadS [DescribeAggregateIdFormatResponse]
$creadList :: ReadS [DescribeAggregateIdFormatResponse]
readsPrec :: Int -> ReadS DescribeAggregateIdFormatResponse
$creadsPrec :: Int -> ReadS DescribeAggregateIdFormatResponse
Prelude.Read, Int -> DescribeAggregateIdFormatResponse -> ShowS
[DescribeAggregateIdFormatResponse] -> ShowS
DescribeAggregateIdFormatResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAggregateIdFormatResponse] -> ShowS
$cshowList :: [DescribeAggregateIdFormatResponse] -> ShowS
show :: DescribeAggregateIdFormatResponse -> String
$cshow :: DescribeAggregateIdFormatResponse -> String
showsPrec :: Int -> DescribeAggregateIdFormatResponse -> ShowS
$cshowsPrec :: Int -> DescribeAggregateIdFormatResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeAggregateIdFormatResponse x
-> DescribeAggregateIdFormatResponse
forall x.
DescribeAggregateIdFormatResponse
-> Rep DescribeAggregateIdFormatResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAggregateIdFormatResponse x
-> DescribeAggregateIdFormatResponse
$cfrom :: forall x.
DescribeAggregateIdFormatResponse
-> Rep DescribeAggregateIdFormatResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAggregateIdFormatResponse' 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:
--
-- 'statuses', 'describeAggregateIdFormatResponse_statuses' - Information about each resource\'s ID format.
--
-- 'useLongIdsAggregated', 'describeAggregateIdFormatResponse_useLongIdsAggregated' - Indicates whether all resource types in the Region are configured to use
-- longer IDs. This value is only @true@ if all users are configured to use
-- longer IDs for all resources types in the Region.
--
-- 'httpStatus', 'describeAggregateIdFormatResponse_httpStatus' - The response's http status code.
newDescribeAggregateIdFormatResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeAggregateIdFormatResponse
newDescribeAggregateIdFormatResponse :: Int -> DescribeAggregateIdFormatResponse
newDescribeAggregateIdFormatResponse Int
pHttpStatus_ =
  DescribeAggregateIdFormatResponse'
    { $sel:statuses:DescribeAggregateIdFormatResponse' :: Maybe [IdFormat]
statuses =
        forall a. Maybe a
Prelude.Nothing,
      $sel:useLongIdsAggregated:DescribeAggregateIdFormatResponse' :: Maybe Bool
useLongIdsAggregated = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeAggregateIdFormatResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about each resource\'s ID format.
describeAggregateIdFormatResponse_statuses :: Lens.Lens' DescribeAggregateIdFormatResponse (Prelude.Maybe [IdFormat])
describeAggregateIdFormatResponse_statuses :: Lens' DescribeAggregateIdFormatResponse (Maybe [IdFormat])
describeAggregateIdFormatResponse_statuses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAggregateIdFormatResponse' {Maybe [IdFormat]
statuses :: Maybe [IdFormat]
$sel:statuses:DescribeAggregateIdFormatResponse' :: DescribeAggregateIdFormatResponse -> Maybe [IdFormat]
statuses} -> Maybe [IdFormat]
statuses) (\s :: DescribeAggregateIdFormatResponse
s@DescribeAggregateIdFormatResponse' {} Maybe [IdFormat]
a -> DescribeAggregateIdFormatResponse
s {$sel:statuses:DescribeAggregateIdFormatResponse' :: Maybe [IdFormat]
statuses = Maybe [IdFormat]
a} :: DescribeAggregateIdFormatResponse) 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

-- | Indicates whether all resource types in the Region are configured to use
-- longer IDs. This value is only @true@ if all users are configured to use
-- longer IDs for all resources types in the Region.
describeAggregateIdFormatResponse_useLongIdsAggregated :: Lens.Lens' DescribeAggregateIdFormatResponse (Prelude.Maybe Prelude.Bool)
describeAggregateIdFormatResponse_useLongIdsAggregated :: Lens' DescribeAggregateIdFormatResponse (Maybe Bool)
describeAggregateIdFormatResponse_useLongIdsAggregated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAggregateIdFormatResponse' {Maybe Bool
useLongIdsAggregated :: Maybe Bool
$sel:useLongIdsAggregated:DescribeAggregateIdFormatResponse' :: DescribeAggregateIdFormatResponse -> Maybe Bool
useLongIdsAggregated} -> Maybe Bool
useLongIdsAggregated) (\s :: DescribeAggregateIdFormatResponse
s@DescribeAggregateIdFormatResponse' {} Maybe Bool
a -> DescribeAggregateIdFormatResponse
s {$sel:useLongIdsAggregated:DescribeAggregateIdFormatResponse' :: Maybe Bool
useLongIdsAggregated = Maybe Bool
a} :: DescribeAggregateIdFormatResponse)

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

instance
  Prelude.NFData
    DescribeAggregateIdFormatResponse
  where
  rnf :: DescribeAggregateIdFormatResponse -> ()
rnf DescribeAggregateIdFormatResponse' {Int
Maybe Bool
Maybe [IdFormat]
httpStatus :: Int
useLongIdsAggregated :: Maybe Bool
statuses :: Maybe [IdFormat]
$sel:httpStatus:DescribeAggregateIdFormatResponse' :: DescribeAggregateIdFormatResponse -> Int
$sel:useLongIdsAggregated:DescribeAggregateIdFormatResponse' :: DescribeAggregateIdFormatResponse -> Maybe Bool
$sel:statuses:DescribeAggregateIdFormatResponse' :: DescribeAggregateIdFormatResponse -> Maybe [IdFormat]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [IdFormat]
statuses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
useLongIdsAggregated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus