{-# 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.GetApiCache
-- 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 an @ApiCache@ object.
module Amazonka.AppSync.GetApiCache
  ( -- * Creating a Request
    GetApiCache (..),
    newGetApiCache,

    -- * Request Lenses
    getApiCache_apiId,

    -- * Destructuring the Response
    GetApiCacheResponse (..),
    newGetApiCacheResponse,

    -- * Response Lenses
    getApiCacheResponse_apiCache,
    getApiCacheResponse_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

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

-- |
-- Create a value of 'GetApiCache' 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', 'getApiCache_apiId' - The API ID.
newGetApiCache ::
  -- | 'apiId'
  Prelude.Text ->
  GetApiCache
newGetApiCache :: Text -> GetApiCache
newGetApiCache Text
pApiId_ =
  GetApiCache' {$sel:apiId:GetApiCache' :: Text
apiId = Text
pApiId_}

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

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

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

instance Data.ToHeaders GetApiCache where
  toHeaders :: GetApiCache -> 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 GetApiCache where
  toPath :: GetApiCache -> ByteString
toPath GetApiCache' {Text
apiId :: Text
$sel:apiId:GetApiCache' :: GetApiCache -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/apis/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
apiId, ByteString
"/ApiCaches"]

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

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

-- |
-- Create a value of 'GetApiCacheResponse' 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:
--
-- 'apiCache', 'getApiCacheResponse_apiCache' - The @ApiCache@ object.
--
-- 'httpStatus', 'getApiCacheResponse_httpStatus' - The response's http status code.
newGetApiCacheResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetApiCacheResponse
newGetApiCacheResponse :: Int -> GetApiCacheResponse
newGetApiCacheResponse Int
pHttpStatus_ =
  GetApiCacheResponse'
    { $sel:apiCache:GetApiCacheResponse' :: Maybe ApiCache
apiCache = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetApiCacheResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @ApiCache@ object.
getApiCacheResponse_apiCache :: Lens.Lens' GetApiCacheResponse (Prelude.Maybe ApiCache)
getApiCacheResponse_apiCache :: Lens' GetApiCacheResponse (Maybe ApiCache)
getApiCacheResponse_apiCache = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApiCacheResponse' {Maybe ApiCache
apiCache :: Maybe ApiCache
$sel:apiCache:GetApiCacheResponse' :: GetApiCacheResponse -> Maybe ApiCache
apiCache} -> Maybe ApiCache
apiCache) (\s :: GetApiCacheResponse
s@GetApiCacheResponse' {} Maybe ApiCache
a -> GetApiCacheResponse
s {$sel:apiCache:GetApiCacheResponse' :: Maybe ApiCache
apiCache = Maybe ApiCache
a} :: GetApiCacheResponse)

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

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