{-# 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.AppSync.GetGraphqlApi
-- 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 a @GraphqlApi@ object.
module Amazonka.AppSync.GetGraphqlApi
  ( -- * Creating a Request
    GetGraphqlApi (..),
    newGetGraphqlApi,

    -- * Request Lenses
    getGraphqlApi_apiId,

    -- * Destructuring the Response
    GetGraphqlApiResponse (..),
    newGetGraphqlApiResponse,

    -- * Response Lenses
    getGraphqlApiResponse_graphqlApi,
    getGraphqlApiResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'GetGraphqlApi' 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:
--
-- 'apiId', 'getGraphqlApi_apiId' - The API ID for the GraphQL API.
newGetGraphqlApi ::
  -- | 'apiId'
  Prelude.Text ->
  GetGraphqlApi
newGetGraphqlApi :: Text -> GetGraphqlApi
newGetGraphqlApi Text
pApiId_ =
  GetGraphqlApi' {$sel:apiId:GetGraphqlApi' :: Text
apiId = Text
pApiId_}

-- | The API ID for the GraphQL API.
getGraphqlApi_apiId :: Lens.Lens' GetGraphqlApi Prelude.Text
getGraphqlApi_apiId :: Lens' GetGraphqlApi Text
getGraphqlApi_apiId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGraphqlApi' {Text
apiId :: Text
$sel:apiId:GetGraphqlApi' :: GetGraphqlApi -> Text
apiId} -> Text
apiId) (\s :: GetGraphqlApi
s@GetGraphqlApi' {} Text
a -> GetGraphqlApi
s {$sel:apiId:GetGraphqlApi' :: Text
apiId = Text
a} :: GetGraphqlApi)

instance Core.AWSRequest GetGraphqlApi where
  type
    AWSResponse GetGraphqlApi =
      GetGraphqlApiResponse
  request :: (Service -> Service) -> GetGraphqlApi -> Request GetGraphqlApi
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 GetGraphqlApi
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetGraphqlApi)))
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 GraphqlApi -> Int -> GetGraphqlApiResponse
GetGraphqlApiResponse'
            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
"graphqlApi")
            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 GetGraphqlApi where
  hashWithSalt :: Int -> GetGraphqlApi -> Int
hashWithSalt Int
_salt GetGraphqlApi' {Text
apiId :: Text
$sel:apiId:GetGraphqlApi' :: GetGraphqlApi -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
apiId

instance Prelude.NFData GetGraphqlApi where
  rnf :: GetGraphqlApi -> ()
rnf GetGraphqlApi' {Text
apiId :: Text
$sel:apiId:GetGraphqlApi' :: GetGraphqlApi -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
apiId

instance Data.ToHeaders GetGraphqlApi where
  toHeaders :: GetGraphqlApi -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath GetGraphqlApi where
  toPath :: GetGraphqlApi -> ByteString
toPath GetGraphqlApi' {Text
apiId :: Text
$sel:apiId:GetGraphqlApi' :: GetGraphqlApi -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/v1/apis/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
apiId]

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

-- | /See:/ 'newGetGraphqlApiResponse' smart constructor.
data GetGraphqlApiResponse = GetGraphqlApiResponse'
  { -- | The @GraphqlApi@ object.
    GetGraphqlApiResponse -> Maybe GraphqlApi
graphqlApi :: Prelude.Maybe GraphqlApi,
    -- | The response's http status code.
    GetGraphqlApiResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetGraphqlApiResponse -> GetGraphqlApiResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGraphqlApiResponse -> GetGraphqlApiResponse -> Bool
$c/= :: GetGraphqlApiResponse -> GetGraphqlApiResponse -> Bool
== :: GetGraphqlApiResponse -> GetGraphqlApiResponse -> Bool
$c== :: GetGraphqlApiResponse -> GetGraphqlApiResponse -> Bool
Prelude.Eq, ReadPrec [GetGraphqlApiResponse]
ReadPrec GetGraphqlApiResponse
Int -> ReadS GetGraphqlApiResponse
ReadS [GetGraphqlApiResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetGraphqlApiResponse]
$creadListPrec :: ReadPrec [GetGraphqlApiResponse]
readPrec :: ReadPrec GetGraphqlApiResponse
$creadPrec :: ReadPrec GetGraphqlApiResponse
readList :: ReadS [GetGraphqlApiResponse]
$creadList :: ReadS [GetGraphqlApiResponse]
readsPrec :: Int -> ReadS GetGraphqlApiResponse
$creadsPrec :: Int -> ReadS GetGraphqlApiResponse
Prelude.Read, Int -> GetGraphqlApiResponse -> ShowS
[GetGraphqlApiResponse] -> ShowS
GetGraphqlApiResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGraphqlApiResponse] -> ShowS
$cshowList :: [GetGraphqlApiResponse] -> ShowS
show :: GetGraphqlApiResponse -> String
$cshow :: GetGraphqlApiResponse -> String
showsPrec :: Int -> GetGraphqlApiResponse -> ShowS
$cshowsPrec :: Int -> GetGraphqlApiResponse -> ShowS
Prelude.Show, forall x. Rep GetGraphqlApiResponse x -> GetGraphqlApiResponse
forall x. GetGraphqlApiResponse -> Rep GetGraphqlApiResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetGraphqlApiResponse x -> GetGraphqlApiResponse
$cfrom :: forall x. GetGraphqlApiResponse -> Rep GetGraphqlApiResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetGraphqlApiResponse' 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:
--
-- 'graphqlApi', 'getGraphqlApiResponse_graphqlApi' - The @GraphqlApi@ object.
--
-- 'httpStatus', 'getGraphqlApiResponse_httpStatus' - The response's http status code.
newGetGraphqlApiResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetGraphqlApiResponse
newGetGraphqlApiResponse :: Int -> GetGraphqlApiResponse
newGetGraphqlApiResponse Int
pHttpStatus_ =
  GetGraphqlApiResponse'
    { $sel:graphqlApi:GetGraphqlApiResponse' :: Maybe GraphqlApi
graphqlApi =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetGraphqlApiResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @GraphqlApi@ object.
getGraphqlApiResponse_graphqlApi :: Lens.Lens' GetGraphqlApiResponse (Prelude.Maybe GraphqlApi)
getGraphqlApiResponse_graphqlApi :: Lens' GetGraphqlApiResponse (Maybe GraphqlApi)
getGraphqlApiResponse_graphqlApi = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGraphqlApiResponse' {Maybe GraphqlApi
graphqlApi :: Maybe GraphqlApi
$sel:graphqlApi:GetGraphqlApiResponse' :: GetGraphqlApiResponse -> Maybe GraphqlApi
graphqlApi} -> Maybe GraphqlApi
graphqlApi) (\s :: GetGraphqlApiResponse
s@GetGraphqlApiResponse' {} Maybe GraphqlApi
a -> GetGraphqlApiResponse
s {$sel:graphqlApi:GetGraphqlApiResponse' :: Maybe GraphqlApi
graphqlApi = Maybe GraphqlApi
a} :: GetGraphqlApiResponse)

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

instance Prelude.NFData GetGraphqlApiResponse where
  rnf :: GetGraphqlApiResponse -> ()
rnf GetGraphqlApiResponse' {Int
Maybe GraphqlApi
httpStatus :: Int
graphqlApi :: Maybe GraphqlApi
$sel:httpStatus:GetGraphqlApiResponse' :: GetGraphqlApiResponse -> Int
$sel:graphqlApi:GetGraphqlApiResponse' :: GetGraphqlApiResponse -> Maybe GraphqlApi
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe GraphqlApi
graphqlApi
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus