{-# 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.APIGateway.GetSdkTypes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets SDK types
--
-- This operation returns paginated results.
module Amazonka.APIGateway.GetSdkTypes
  ( -- * Creating a Request
    GetSdkTypes (..),
    newGetSdkTypes,

    -- * Request Lenses
    getSdkTypes_limit,
    getSdkTypes_position,

    -- * Destructuring the Response
    GetSdkTypesResponse (..),
    newGetSdkTypesResponse,

    -- * Response Lenses
    getSdkTypesResponse_items,
    getSdkTypesResponse_position,
    getSdkTypesResponse_httpStatus,
  )
where

import Amazonka.APIGateway.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

-- | Get the SdkTypes collection.
--
-- /See:/ 'newGetSdkTypes' smart constructor.
data GetSdkTypes = GetSdkTypes'
  { -- | The maximum number of returned results per page. The default value is 25
    -- and the maximum value is 500.
    GetSdkTypes -> Maybe Int
limit :: Prelude.Maybe Prelude.Int,
    -- | The current pagination position in the paged result set.
    GetSdkTypes -> Maybe Text
position :: Prelude.Maybe Prelude.Text
  }
  deriving (GetSdkTypes -> GetSdkTypes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSdkTypes -> GetSdkTypes -> Bool
$c/= :: GetSdkTypes -> GetSdkTypes -> Bool
== :: GetSdkTypes -> GetSdkTypes -> Bool
$c== :: GetSdkTypes -> GetSdkTypes -> Bool
Prelude.Eq, ReadPrec [GetSdkTypes]
ReadPrec GetSdkTypes
Int -> ReadS GetSdkTypes
ReadS [GetSdkTypes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSdkTypes]
$creadListPrec :: ReadPrec [GetSdkTypes]
readPrec :: ReadPrec GetSdkTypes
$creadPrec :: ReadPrec GetSdkTypes
readList :: ReadS [GetSdkTypes]
$creadList :: ReadS [GetSdkTypes]
readsPrec :: Int -> ReadS GetSdkTypes
$creadsPrec :: Int -> ReadS GetSdkTypes
Prelude.Read, Int -> GetSdkTypes -> ShowS
[GetSdkTypes] -> ShowS
GetSdkTypes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSdkTypes] -> ShowS
$cshowList :: [GetSdkTypes] -> ShowS
show :: GetSdkTypes -> String
$cshow :: GetSdkTypes -> String
showsPrec :: Int -> GetSdkTypes -> ShowS
$cshowsPrec :: Int -> GetSdkTypes -> ShowS
Prelude.Show, forall x. Rep GetSdkTypes x -> GetSdkTypes
forall x. GetSdkTypes -> Rep GetSdkTypes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSdkTypes x -> GetSdkTypes
$cfrom :: forall x. GetSdkTypes -> Rep GetSdkTypes x
Prelude.Generic)

-- |
-- Create a value of 'GetSdkTypes' 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:
--
-- 'limit', 'getSdkTypes_limit' - The maximum number of returned results per page. The default value is 25
-- and the maximum value is 500.
--
-- 'position', 'getSdkTypes_position' - The current pagination position in the paged result set.
newGetSdkTypes ::
  GetSdkTypes
newGetSdkTypes :: GetSdkTypes
newGetSdkTypes =
  GetSdkTypes'
    { $sel:limit:GetSdkTypes' :: Maybe Int
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:position:GetSdkTypes' :: Maybe Text
position = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of returned results per page. The default value is 25
-- and the maximum value is 500.
getSdkTypes_limit :: Lens.Lens' GetSdkTypes (Prelude.Maybe Prelude.Int)
getSdkTypes_limit :: Lens' GetSdkTypes (Maybe Int)
getSdkTypes_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSdkTypes' {Maybe Int
limit :: Maybe Int
$sel:limit:GetSdkTypes' :: GetSdkTypes -> Maybe Int
limit} -> Maybe Int
limit) (\s :: GetSdkTypes
s@GetSdkTypes' {} Maybe Int
a -> GetSdkTypes
s {$sel:limit:GetSdkTypes' :: Maybe Int
limit = Maybe Int
a} :: GetSdkTypes)

-- | The current pagination position in the paged result set.
getSdkTypes_position :: Lens.Lens' GetSdkTypes (Prelude.Maybe Prelude.Text)
getSdkTypes_position :: Lens' GetSdkTypes (Maybe Text)
getSdkTypes_position = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSdkTypes' {Maybe Text
position :: Maybe Text
$sel:position:GetSdkTypes' :: GetSdkTypes -> Maybe Text
position} -> Maybe Text
position) (\s :: GetSdkTypes
s@GetSdkTypes' {} Maybe Text
a -> GetSdkTypes
s {$sel:position:GetSdkTypes' :: Maybe Text
position = Maybe Text
a} :: GetSdkTypes)

instance Core.AWSPager GetSdkTypes where
  page :: GetSdkTypes -> AWSResponse GetSdkTypes -> Maybe GetSdkTypes
page GetSdkTypes
rq AWSResponse GetSdkTypes
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetSdkTypes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetSdkTypesResponse (Maybe Text)
getSdkTypesResponse_position
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetSdkTypes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetSdkTypesResponse (Maybe [SdkType])
getSdkTypesResponse_items
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ GetSdkTypes
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetSdkTypes (Maybe Text)
getSdkTypes_position
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetSdkTypes
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetSdkTypesResponse (Maybe Text)
getSdkTypesResponse_position
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest GetSdkTypes where
  type AWSResponse GetSdkTypes = GetSdkTypesResponse
  request :: (Service -> Service) -> GetSdkTypes -> Request GetSdkTypes
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 GetSdkTypes
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetSdkTypes)))
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 [SdkType] -> Maybe Text -> Int -> GetSdkTypesResponse
GetSdkTypesResponse'
            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
"item" 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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"position")
            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 GetSdkTypes where
  hashWithSalt :: Int -> GetSdkTypes -> Int
hashWithSalt Int
_salt GetSdkTypes' {Maybe Int
Maybe Text
position :: Maybe Text
limit :: Maybe Int
$sel:position:GetSdkTypes' :: GetSdkTypes -> Maybe Text
$sel:limit:GetSdkTypes' :: GetSdkTypes -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
position

instance Prelude.NFData GetSdkTypes where
  rnf :: GetSdkTypes -> ()
rnf GetSdkTypes' {Maybe Int
Maybe Text
position :: Maybe Text
limit :: Maybe Int
$sel:position:GetSdkTypes' :: GetSdkTypes -> Maybe Text
$sel:limit:GetSdkTypes' :: GetSdkTypes -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
position

instance Data.ToHeaders GetSdkTypes where
  toHeaders :: GetSdkTypes -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Accept"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/json" :: Prelude.ByteString)
          ]
      )

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

instance Data.ToQuery GetSdkTypes where
  toQuery :: GetSdkTypes -> QueryString
toQuery GetSdkTypes' {Maybe Int
Maybe Text
position :: Maybe Text
limit :: Maybe Int
$sel:position:GetSdkTypes' :: GetSdkTypes -> Maybe Text
$sel:limit:GetSdkTypes' :: GetSdkTypes -> Maybe Int
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"limit" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
limit, ByteString
"position" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
position]

-- | The collection of SdkType instances.
--
-- /See:/ 'newGetSdkTypesResponse' smart constructor.
data GetSdkTypesResponse = GetSdkTypesResponse'
  { -- | The current page of elements from this collection.
    GetSdkTypesResponse -> Maybe [SdkType]
items :: Prelude.Maybe [SdkType],
    GetSdkTypesResponse -> Maybe Text
position :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetSdkTypesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSdkTypesResponse -> GetSdkTypesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSdkTypesResponse -> GetSdkTypesResponse -> Bool
$c/= :: GetSdkTypesResponse -> GetSdkTypesResponse -> Bool
== :: GetSdkTypesResponse -> GetSdkTypesResponse -> Bool
$c== :: GetSdkTypesResponse -> GetSdkTypesResponse -> Bool
Prelude.Eq, ReadPrec [GetSdkTypesResponse]
ReadPrec GetSdkTypesResponse
Int -> ReadS GetSdkTypesResponse
ReadS [GetSdkTypesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSdkTypesResponse]
$creadListPrec :: ReadPrec [GetSdkTypesResponse]
readPrec :: ReadPrec GetSdkTypesResponse
$creadPrec :: ReadPrec GetSdkTypesResponse
readList :: ReadS [GetSdkTypesResponse]
$creadList :: ReadS [GetSdkTypesResponse]
readsPrec :: Int -> ReadS GetSdkTypesResponse
$creadsPrec :: Int -> ReadS GetSdkTypesResponse
Prelude.Read, Int -> GetSdkTypesResponse -> ShowS
[GetSdkTypesResponse] -> ShowS
GetSdkTypesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSdkTypesResponse] -> ShowS
$cshowList :: [GetSdkTypesResponse] -> ShowS
show :: GetSdkTypesResponse -> String
$cshow :: GetSdkTypesResponse -> String
showsPrec :: Int -> GetSdkTypesResponse -> ShowS
$cshowsPrec :: Int -> GetSdkTypesResponse -> ShowS
Prelude.Show, forall x. Rep GetSdkTypesResponse x -> GetSdkTypesResponse
forall x. GetSdkTypesResponse -> Rep GetSdkTypesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSdkTypesResponse x -> GetSdkTypesResponse
$cfrom :: forall x. GetSdkTypesResponse -> Rep GetSdkTypesResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSdkTypesResponse' 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:
--
-- 'items', 'getSdkTypesResponse_items' - The current page of elements from this collection.
--
-- 'position', 'getSdkTypesResponse_position' - Undocumented member.
--
-- 'httpStatus', 'getSdkTypesResponse_httpStatus' - The response's http status code.
newGetSdkTypesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSdkTypesResponse
newGetSdkTypesResponse :: Int -> GetSdkTypesResponse
newGetSdkTypesResponse Int
pHttpStatus_ =
  GetSdkTypesResponse'
    { $sel:items:GetSdkTypesResponse' :: Maybe [SdkType]
items = forall a. Maybe a
Prelude.Nothing,
      $sel:position:GetSdkTypesResponse' :: Maybe Text
position = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSdkTypesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The current page of elements from this collection.
getSdkTypesResponse_items :: Lens.Lens' GetSdkTypesResponse (Prelude.Maybe [SdkType])
getSdkTypesResponse_items :: Lens' GetSdkTypesResponse (Maybe [SdkType])
getSdkTypesResponse_items = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSdkTypesResponse' {Maybe [SdkType]
items :: Maybe [SdkType]
$sel:items:GetSdkTypesResponse' :: GetSdkTypesResponse -> Maybe [SdkType]
items} -> Maybe [SdkType]
items) (\s :: GetSdkTypesResponse
s@GetSdkTypesResponse' {} Maybe [SdkType]
a -> GetSdkTypesResponse
s {$sel:items:GetSdkTypesResponse' :: Maybe [SdkType]
items = Maybe [SdkType]
a} :: GetSdkTypesResponse) 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

-- | Undocumented member.
getSdkTypesResponse_position :: Lens.Lens' GetSdkTypesResponse (Prelude.Maybe Prelude.Text)
getSdkTypesResponse_position :: Lens' GetSdkTypesResponse (Maybe Text)
getSdkTypesResponse_position = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSdkTypesResponse' {Maybe Text
position :: Maybe Text
$sel:position:GetSdkTypesResponse' :: GetSdkTypesResponse -> Maybe Text
position} -> Maybe Text
position) (\s :: GetSdkTypesResponse
s@GetSdkTypesResponse' {} Maybe Text
a -> GetSdkTypesResponse
s {$sel:position:GetSdkTypesResponse' :: Maybe Text
position = Maybe Text
a} :: GetSdkTypesResponse)

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

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