{-# 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.Glue.GetBlueprint
-- 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 the details of a blueprint.
module Amazonka.Glue.GetBlueprint
  ( -- * Creating a Request
    GetBlueprint (..),
    newGetBlueprint,

    -- * Request Lenses
    getBlueprint_includeBlueprint,
    getBlueprint_includeParameterSpec,
    getBlueprint_name,

    -- * Destructuring the Response
    GetBlueprintResponse (..),
    newGetBlueprintResponse,

    -- * Response Lenses
    getBlueprintResponse_blueprint,
    getBlueprintResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetBlueprint' smart constructor.
data GetBlueprint = GetBlueprint'
  { -- | Specifies whether or not to include the blueprint in the response.
    GetBlueprint -> Maybe Bool
includeBlueprint :: Prelude.Maybe Prelude.Bool,
    -- | Specifies whether or not to include the parameter specification.
    GetBlueprint -> Maybe Bool
includeParameterSpec :: Prelude.Maybe Prelude.Bool,
    -- | The name of the blueprint.
    GetBlueprint -> Text
name :: Prelude.Text
  }
  deriving (GetBlueprint -> GetBlueprint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBlueprint -> GetBlueprint -> Bool
$c/= :: GetBlueprint -> GetBlueprint -> Bool
== :: GetBlueprint -> GetBlueprint -> Bool
$c== :: GetBlueprint -> GetBlueprint -> Bool
Prelude.Eq, ReadPrec [GetBlueprint]
ReadPrec GetBlueprint
Int -> ReadS GetBlueprint
ReadS [GetBlueprint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBlueprint]
$creadListPrec :: ReadPrec [GetBlueprint]
readPrec :: ReadPrec GetBlueprint
$creadPrec :: ReadPrec GetBlueprint
readList :: ReadS [GetBlueprint]
$creadList :: ReadS [GetBlueprint]
readsPrec :: Int -> ReadS GetBlueprint
$creadsPrec :: Int -> ReadS GetBlueprint
Prelude.Read, Int -> GetBlueprint -> ShowS
[GetBlueprint] -> ShowS
GetBlueprint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBlueprint] -> ShowS
$cshowList :: [GetBlueprint] -> ShowS
show :: GetBlueprint -> String
$cshow :: GetBlueprint -> String
showsPrec :: Int -> GetBlueprint -> ShowS
$cshowsPrec :: Int -> GetBlueprint -> ShowS
Prelude.Show, forall x. Rep GetBlueprint x -> GetBlueprint
forall x. GetBlueprint -> Rep GetBlueprint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBlueprint x -> GetBlueprint
$cfrom :: forall x. GetBlueprint -> Rep GetBlueprint x
Prelude.Generic)

-- |
-- Create a value of 'GetBlueprint' 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:
--
-- 'includeBlueprint', 'getBlueprint_includeBlueprint' - Specifies whether or not to include the blueprint in the response.
--
-- 'includeParameterSpec', 'getBlueprint_includeParameterSpec' - Specifies whether or not to include the parameter specification.
--
-- 'name', 'getBlueprint_name' - The name of the blueprint.
newGetBlueprint ::
  -- | 'name'
  Prelude.Text ->
  GetBlueprint
newGetBlueprint :: Text -> GetBlueprint
newGetBlueprint Text
pName_ =
  GetBlueprint'
    { $sel:includeBlueprint:GetBlueprint' :: Maybe Bool
includeBlueprint = forall a. Maybe a
Prelude.Nothing,
      $sel:includeParameterSpec:GetBlueprint' :: Maybe Bool
includeParameterSpec = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetBlueprint' :: Text
name = Text
pName_
    }

-- | Specifies whether or not to include the blueprint in the response.
getBlueprint_includeBlueprint :: Lens.Lens' GetBlueprint (Prelude.Maybe Prelude.Bool)
getBlueprint_includeBlueprint :: Lens' GetBlueprint (Maybe Bool)
getBlueprint_includeBlueprint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprint' {Maybe Bool
includeBlueprint :: Maybe Bool
$sel:includeBlueprint:GetBlueprint' :: GetBlueprint -> Maybe Bool
includeBlueprint} -> Maybe Bool
includeBlueprint) (\s :: GetBlueprint
s@GetBlueprint' {} Maybe Bool
a -> GetBlueprint
s {$sel:includeBlueprint:GetBlueprint' :: Maybe Bool
includeBlueprint = Maybe Bool
a} :: GetBlueprint)

-- | Specifies whether or not to include the parameter specification.
getBlueprint_includeParameterSpec :: Lens.Lens' GetBlueprint (Prelude.Maybe Prelude.Bool)
getBlueprint_includeParameterSpec :: Lens' GetBlueprint (Maybe Bool)
getBlueprint_includeParameterSpec = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprint' {Maybe Bool
includeParameterSpec :: Maybe Bool
$sel:includeParameterSpec:GetBlueprint' :: GetBlueprint -> Maybe Bool
includeParameterSpec} -> Maybe Bool
includeParameterSpec) (\s :: GetBlueprint
s@GetBlueprint' {} Maybe Bool
a -> GetBlueprint
s {$sel:includeParameterSpec:GetBlueprint' :: Maybe Bool
includeParameterSpec = Maybe Bool
a} :: GetBlueprint)

-- | The name of the blueprint.
getBlueprint_name :: Lens.Lens' GetBlueprint Prelude.Text
getBlueprint_name :: Lens' GetBlueprint Text
getBlueprint_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprint' {Text
name :: Text
$sel:name:GetBlueprint' :: GetBlueprint -> Text
name} -> Text
name) (\s :: GetBlueprint
s@GetBlueprint' {} Text
a -> GetBlueprint
s {$sel:name:GetBlueprint' :: Text
name = Text
a} :: GetBlueprint)

instance Core.AWSRequest GetBlueprint where
  type AWSResponse GetBlueprint = GetBlueprintResponse
  request :: (Service -> Service) -> GetBlueprint -> Request GetBlueprint
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 GetBlueprint
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetBlueprint)))
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 Blueprint -> Int -> GetBlueprintResponse
GetBlueprintResponse'
            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
"Blueprint")
            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 GetBlueprint where
  hashWithSalt :: Int -> GetBlueprint -> Int
hashWithSalt Int
_salt GetBlueprint' {Maybe Bool
Text
name :: Text
includeParameterSpec :: Maybe Bool
includeBlueprint :: Maybe Bool
$sel:name:GetBlueprint' :: GetBlueprint -> Text
$sel:includeParameterSpec:GetBlueprint' :: GetBlueprint -> Maybe Bool
$sel:includeBlueprint:GetBlueprint' :: GetBlueprint -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
includeBlueprint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
includeParameterSpec
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData GetBlueprint where
  rnf :: GetBlueprint -> ()
rnf GetBlueprint' {Maybe Bool
Text
name :: Text
includeParameterSpec :: Maybe Bool
includeBlueprint :: Maybe Bool
$sel:name:GetBlueprint' :: GetBlueprint -> Text
$sel:includeParameterSpec:GetBlueprint' :: GetBlueprint -> Maybe Bool
$sel:includeBlueprint:GetBlueprint' :: GetBlueprint -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
includeBlueprint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
includeParameterSpec
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders GetBlueprint where
  toHeaders :: GetBlueprint -> 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
"AWSGlue.GetBlueprint" :: 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 GetBlueprint where
  toJSON :: GetBlueprint -> Value
toJSON GetBlueprint' {Maybe Bool
Text
name :: Text
includeParameterSpec :: Maybe Bool
includeBlueprint :: Maybe Bool
$sel:name:GetBlueprint' :: GetBlueprint -> Text
$sel:includeParameterSpec:GetBlueprint' :: GetBlueprint -> Maybe Bool
$sel:includeBlueprint:GetBlueprint' :: GetBlueprint -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"IncludeBlueprint" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
includeBlueprint,
            (Key
"IncludeParameterSpec" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
includeParameterSpec,
            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 GetBlueprint where
  toPath :: GetBlueprint -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'GetBlueprintResponse' 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:
--
-- 'blueprint', 'getBlueprintResponse_blueprint' - Returns a @Blueprint@ object.
--
-- 'httpStatus', 'getBlueprintResponse_httpStatus' - The response's http status code.
newGetBlueprintResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBlueprintResponse
newGetBlueprintResponse :: Int -> GetBlueprintResponse
newGetBlueprintResponse Int
pHttpStatus_ =
  GetBlueprintResponse'
    { $sel:blueprint:GetBlueprintResponse' :: Maybe Blueprint
blueprint = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBlueprintResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns a @Blueprint@ object.
getBlueprintResponse_blueprint :: Lens.Lens' GetBlueprintResponse (Prelude.Maybe Blueprint)
getBlueprintResponse_blueprint :: Lens' GetBlueprintResponse (Maybe Blueprint)
getBlueprintResponse_blueprint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprintResponse' {Maybe Blueprint
blueprint :: Maybe Blueprint
$sel:blueprint:GetBlueprintResponse' :: GetBlueprintResponse -> Maybe Blueprint
blueprint} -> Maybe Blueprint
blueprint) (\s :: GetBlueprintResponse
s@GetBlueprintResponse' {} Maybe Blueprint
a -> GetBlueprintResponse
s {$sel:blueprint:GetBlueprintResponse' :: Maybe Blueprint
blueprint = Maybe Blueprint
a} :: GetBlueprintResponse)

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

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