{-# 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.GetApiAssociation
-- 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 @ApiAssociation@ object.
module Amazonka.AppSync.GetApiAssociation
  ( -- * Creating a Request
    GetApiAssociation (..),
    newGetApiAssociation,

    -- * Request Lenses
    getApiAssociation_domainName,

    -- * Destructuring the Response
    GetApiAssociationResponse (..),
    newGetApiAssociationResponse,

    -- * Response Lenses
    getApiAssociationResponse_apiAssociation,
    getApiAssociationResponse_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:/ 'newGetApiAssociation' smart constructor.
data GetApiAssociation = GetApiAssociation'
  { -- | The domain name.
    GetApiAssociation -> Text
domainName :: Prelude.Text
  }
  deriving (GetApiAssociation -> GetApiAssociation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetApiAssociation -> GetApiAssociation -> Bool
$c/= :: GetApiAssociation -> GetApiAssociation -> Bool
== :: GetApiAssociation -> GetApiAssociation -> Bool
$c== :: GetApiAssociation -> GetApiAssociation -> Bool
Prelude.Eq, ReadPrec [GetApiAssociation]
ReadPrec GetApiAssociation
Int -> ReadS GetApiAssociation
ReadS [GetApiAssociation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetApiAssociation]
$creadListPrec :: ReadPrec [GetApiAssociation]
readPrec :: ReadPrec GetApiAssociation
$creadPrec :: ReadPrec GetApiAssociation
readList :: ReadS [GetApiAssociation]
$creadList :: ReadS [GetApiAssociation]
readsPrec :: Int -> ReadS GetApiAssociation
$creadsPrec :: Int -> ReadS GetApiAssociation
Prelude.Read, Int -> GetApiAssociation -> ShowS
[GetApiAssociation] -> ShowS
GetApiAssociation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetApiAssociation] -> ShowS
$cshowList :: [GetApiAssociation] -> ShowS
show :: GetApiAssociation -> String
$cshow :: GetApiAssociation -> String
showsPrec :: Int -> GetApiAssociation -> ShowS
$cshowsPrec :: Int -> GetApiAssociation -> ShowS
Prelude.Show, forall x. Rep GetApiAssociation x -> GetApiAssociation
forall x. GetApiAssociation -> Rep GetApiAssociation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetApiAssociation x -> GetApiAssociation
$cfrom :: forall x. GetApiAssociation -> Rep GetApiAssociation x
Prelude.Generic)

-- |
-- Create a value of 'GetApiAssociation' 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:
--
-- 'domainName', 'getApiAssociation_domainName' - The domain name.
newGetApiAssociation ::
  -- | 'domainName'
  Prelude.Text ->
  GetApiAssociation
newGetApiAssociation :: Text -> GetApiAssociation
newGetApiAssociation Text
pDomainName_ =
  GetApiAssociation' {$sel:domainName:GetApiAssociation' :: Text
domainName = Text
pDomainName_}

-- | The domain name.
getApiAssociation_domainName :: Lens.Lens' GetApiAssociation Prelude.Text
getApiAssociation_domainName :: Lens' GetApiAssociation Text
getApiAssociation_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApiAssociation' {Text
domainName :: Text
$sel:domainName:GetApiAssociation' :: GetApiAssociation -> Text
domainName} -> Text
domainName) (\s :: GetApiAssociation
s@GetApiAssociation' {} Text
a -> GetApiAssociation
s {$sel:domainName:GetApiAssociation' :: Text
domainName = Text
a} :: GetApiAssociation)

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

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

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

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

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

-- |
-- Create a value of 'GetApiAssociationResponse' 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:
--
-- 'apiAssociation', 'getApiAssociationResponse_apiAssociation' - The @ApiAssociation@ object.
--
-- 'httpStatus', 'getApiAssociationResponse_httpStatus' - The response's http status code.
newGetApiAssociationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetApiAssociationResponse
newGetApiAssociationResponse :: Int -> GetApiAssociationResponse
newGetApiAssociationResponse Int
pHttpStatus_ =
  GetApiAssociationResponse'
    { $sel:apiAssociation:GetApiAssociationResponse' :: Maybe ApiAssociation
apiAssociation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetApiAssociationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The @ApiAssociation@ object.
getApiAssociationResponse_apiAssociation :: Lens.Lens' GetApiAssociationResponse (Prelude.Maybe ApiAssociation)
getApiAssociationResponse_apiAssociation :: Lens' GetApiAssociationResponse (Maybe ApiAssociation)
getApiAssociationResponse_apiAssociation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetApiAssociationResponse' {Maybe ApiAssociation
apiAssociation :: Maybe ApiAssociation
$sel:apiAssociation:GetApiAssociationResponse' :: GetApiAssociationResponse -> Maybe ApiAssociation
apiAssociation} -> Maybe ApiAssociation
apiAssociation) (\s :: GetApiAssociationResponse
s@GetApiAssociationResponse' {} Maybe ApiAssociation
a -> GetApiAssociationResponse
s {$sel:apiAssociation:GetApiAssociationResponse' :: Maybe ApiAssociation
apiAssociation = Maybe ApiAssociation
a} :: GetApiAssociationResponse)

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

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