{-# 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.Athena.GetDataCatalog
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the specified data catalog.
module Amazonka.Athena.GetDataCatalog
  ( -- * Creating a Request
    GetDataCatalog (..),
    newGetDataCatalog,

    -- * Request Lenses
    getDataCatalog_name,

    -- * Destructuring the Response
    GetDataCatalogResponse (..),
    newGetDataCatalogResponse,

    -- * Response Lenses
    getDataCatalogResponse_dataCatalog,
    getDataCatalogResponse_httpStatus,
  )
where

import Amazonka.Athena.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:/ 'newGetDataCatalog' smart constructor.
data GetDataCatalog = GetDataCatalog'
  { -- | The name of the data catalog to return.
    GetDataCatalog -> Text
name :: Prelude.Text
  }
  deriving (GetDataCatalog -> GetDataCatalog -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDataCatalog -> GetDataCatalog -> Bool
$c/= :: GetDataCatalog -> GetDataCatalog -> Bool
== :: GetDataCatalog -> GetDataCatalog -> Bool
$c== :: GetDataCatalog -> GetDataCatalog -> Bool
Prelude.Eq, ReadPrec [GetDataCatalog]
ReadPrec GetDataCatalog
Int -> ReadS GetDataCatalog
ReadS [GetDataCatalog]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDataCatalog]
$creadListPrec :: ReadPrec [GetDataCatalog]
readPrec :: ReadPrec GetDataCatalog
$creadPrec :: ReadPrec GetDataCatalog
readList :: ReadS [GetDataCatalog]
$creadList :: ReadS [GetDataCatalog]
readsPrec :: Int -> ReadS GetDataCatalog
$creadsPrec :: Int -> ReadS GetDataCatalog
Prelude.Read, Int -> GetDataCatalog -> ShowS
[GetDataCatalog] -> ShowS
GetDataCatalog -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDataCatalog] -> ShowS
$cshowList :: [GetDataCatalog] -> ShowS
show :: GetDataCatalog -> String
$cshow :: GetDataCatalog -> String
showsPrec :: Int -> GetDataCatalog -> ShowS
$cshowsPrec :: Int -> GetDataCatalog -> ShowS
Prelude.Show, forall x. Rep GetDataCatalog x -> GetDataCatalog
forall x. GetDataCatalog -> Rep GetDataCatalog x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDataCatalog x -> GetDataCatalog
$cfrom :: forall x. GetDataCatalog -> Rep GetDataCatalog x
Prelude.Generic)

-- |
-- Create a value of 'GetDataCatalog' 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:
--
-- 'name', 'getDataCatalog_name' - The name of the data catalog to return.
newGetDataCatalog ::
  -- | 'name'
  Prelude.Text ->
  GetDataCatalog
newGetDataCatalog :: Text -> GetDataCatalog
newGetDataCatalog Text
pName_ =
  GetDataCatalog' {$sel:name:GetDataCatalog' :: Text
name = Text
pName_}

-- | The name of the data catalog to return.
getDataCatalog_name :: Lens.Lens' GetDataCatalog Prelude.Text
getDataCatalog_name :: Lens' GetDataCatalog Text
getDataCatalog_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataCatalog' {Text
name :: Text
$sel:name:GetDataCatalog' :: GetDataCatalog -> Text
name} -> Text
name) (\s :: GetDataCatalog
s@GetDataCatalog' {} Text
a -> GetDataCatalog
s {$sel:name:GetDataCatalog' :: Text
name = Text
a} :: GetDataCatalog)

instance Core.AWSRequest GetDataCatalog where
  type
    AWSResponse GetDataCatalog =
      GetDataCatalogResponse
  request :: (Service -> Service) -> GetDataCatalog -> Request GetDataCatalog
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetDataCatalog
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetDataCatalog)))
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 DataCatalog -> Int -> GetDataCatalogResponse
GetDataCatalogResponse'
            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
"DataCatalog")
            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 GetDataCatalog where
  hashWithSalt :: Int -> GetDataCatalog -> Int
hashWithSalt Int
_salt GetDataCatalog' {Text
name :: Text
$sel:name:GetDataCatalog' :: GetDataCatalog -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

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

instance Data.ToJSON GetDataCatalog where
  toJSON :: GetDataCatalog -> Value
toJSON GetDataCatalog' {Text
name :: Text
$sel:name:GetDataCatalog' :: GetDataCatalog -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)]
      )

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

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

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

-- |
-- Create a value of 'GetDataCatalogResponse' 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:
--
-- 'dataCatalog', 'getDataCatalogResponse_dataCatalog' - The data catalog returned.
--
-- 'httpStatus', 'getDataCatalogResponse_httpStatus' - The response's http status code.
newGetDataCatalogResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDataCatalogResponse
newGetDataCatalogResponse :: Int -> GetDataCatalogResponse
newGetDataCatalogResponse Int
pHttpStatus_ =
  GetDataCatalogResponse'
    { $sel:dataCatalog:GetDataCatalogResponse' :: Maybe DataCatalog
dataCatalog =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetDataCatalogResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The data catalog returned.
getDataCatalogResponse_dataCatalog :: Lens.Lens' GetDataCatalogResponse (Prelude.Maybe DataCatalog)
getDataCatalogResponse_dataCatalog :: Lens' GetDataCatalogResponse (Maybe DataCatalog)
getDataCatalogResponse_dataCatalog = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDataCatalogResponse' {Maybe DataCatalog
dataCatalog :: Maybe DataCatalog
$sel:dataCatalog:GetDataCatalogResponse' :: GetDataCatalogResponse -> Maybe DataCatalog
dataCatalog} -> Maybe DataCatalog
dataCatalog) (\s :: GetDataCatalogResponse
s@GetDataCatalogResponse' {} Maybe DataCatalog
a -> GetDataCatalogResponse
s {$sel:dataCatalog:GetDataCatalogResponse' :: Maybe DataCatalog
dataCatalog = Maybe DataCatalog
a} :: GetDataCatalogResponse)

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

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