{-# 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.GetFunction
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Get a @Function@.
module Amazonka.AppSync.GetFunction
  ( -- * Creating a Request
    GetFunction (..),
    newGetFunction,

    -- * Request Lenses
    getFunction_apiId,
    getFunction_functionId,

    -- * Destructuring the Response
    GetFunctionResponse (..),
    newGetFunctionResponse,

    -- * Response Lenses
    getFunctionResponse_functionConfiguration,
    getFunctionResponse_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:/ 'newGetFunction' smart constructor.
data GetFunction = GetFunction'
  { -- | The GraphQL API ID.
    GetFunction -> Text
apiId :: Prelude.Text,
    -- | The @Function@ ID.
    GetFunction -> Text
functionId :: Prelude.Text
  }
  deriving (GetFunction -> GetFunction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFunction -> GetFunction -> Bool
$c/= :: GetFunction -> GetFunction -> Bool
== :: GetFunction -> GetFunction -> Bool
$c== :: GetFunction -> GetFunction -> Bool
Prelude.Eq, ReadPrec [GetFunction]
ReadPrec GetFunction
Int -> ReadS GetFunction
ReadS [GetFunction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFunction]
$creadListPrec :: ReadPrec [GetFunction]
readPrec :: ReadPrec GetFunction
$creadPrec :: ReadPrec GetFunction
readList :: ReadS [GetFunction]
$creadList :: ReadS [GetFunction]
readsPrec :: Int -> ReadS GetFunction
$creadsPrec :: Int -> ReadS GetFunction
Prelude.Read, Int -> GetFunction -> ShowS
[GetFunction] -> ShowS
GetFunction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFunction] -> ShowS
$cshowList :: [GetFunction] -> ShowS
show :: GetFunction -> String
$cshow :: GetFunction -> String
showsPrec :: Int -> GetFunction -> ShowS
$cshowsPrec :: Int -> GetFunction -> ShowS
Prelude.Show, forall x. Rep GetFunction x -> GetFunction
forall x. GetFunction -> Rep GetFunction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFunction x -> GetFunction
$cfrom :: forall x. GetFunction -> Rep GetFunction x
Prelude.Generic)

-- |
-- Create a value of 'GetFunction' 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', 'getFunction_apiId' - The GraphQL API ID.
--
-- 'functionId', 'getFunction_functionId' - The @Function@ ID.
newGetFunction ::
  -- | 'apiId'
  Prelude.Text ->
  -- | 'functionId'
  Prelude.Text ->
  GetFunction
newGetFunction :: Text -> Text -> GetFunction
newGetFunction Text
pApiId_ Text
pFunctionId_ =
  GetFunction'
    { $sel:apiId:GetFunction' :: Text
apiId = Text
pApiId_,
      $sel:functionId:GetFunction' :: Text
functionId = Text
pFunctionId_
    }

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

-- | The @Function@ ID.
getFunction_functionId :: Lens.Lens' GetFunction Prelude.Text
getFunction_functionId :: Lens' GetFunction Text
getFunction_functionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFunction' {Text
functionId :: Text
$sel:functionId:GetFunction' :: GetFunction -> Text
functionId} -> Text
functionId) (\s :: GetFunction
s@GetFunction' {} Text
a -> GetFunction
s {$sel:functionId:GetFunction' :: Text
functionId = Text
a} :: GetFunction)

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

instance Prelude.NFData GetFunction where
  rnf :: GetFunction -> ()
rnf GetFunction' {Text
functionId :: Text
apiId :: Text
$sel:functionId:GetFunction' :: GetFunction -> Text
$sel:apiId:GetFunction' :: GetFunction -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
apiId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
functionId

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

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

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

-- |
-- Create a value of 'GetFunctionResponse' 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:
--
-- 'functionConfiguration', 'getFunctionResponse_functionConfiguration' - The @Function@ object.
--
-- 'httpStatus', 'getFunctionResponse_httpStatus' - The response's http status code.
newGetFunctionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetFunctionResponse
newGetFunctionResponse :: Int -> GetFunctionResponse
newGetFunctionResponse Int
pHttpStatus_ =
  GetFunctionResponse'
    { $sel:functionConfiguration:GetFunctionResponse' :: Maybe FunctionConfiguration
functionConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetFunctionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @Function@ object.
getFunctionResponse_functionConfiguration :: Lens.Lens' GetFunctionResponse (Prelude.Maybe FunctionConfiguration)
getFunctionResponse_functionConfiguration :: Lens' GetFunctionResponse (Maybe FunctionConfiguration)
getFunctionResponse_functionConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFunctionResponse' {Maybe FunctionConfiguration
functionConfiguration :: Maybe FunctionConfiguration
$sel:functionConfiguration:GetFunctionResponse' :: GetFunctionResponse -> Maybe FunctionConfiguration
functionConfiguration} -> Maybe FunctionConfiguration
functionConfiguration) (\s :: GetFunctionResponse
s@GetFunctionResponse' {} Maybe FunctionConfiguration
a -> GetFunctionResponse
s {$sel:functionConfiguration:GetFunctionResponse' :: Maybe FunctionConfiguration
functionConfiguration = Maybe FunctionConfiguration
a} :: GetFunctionResponse)

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

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