{-# 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.Proton.GetServiceTemplate
-- 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 detailed data for a service template.
module Amazonka.Proton.GetServiceTemplate
  ( -- * Creating a Request
    GetServiceTemplate (..),
    newGetServiceTemplate,

    -- * Request Lenses
    getServiceTemplate_name,

    -- * Destructuring the Response
    GetServiceTemplateResponse (..),
    newGetServiceTemplateResponse,

    -- * Response Lenses
    getServiceTemplateResponse_httpStatus,
    getServiceTemplateResponse_serviceTemplate,
  )
where

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 Amazonka.Proton.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetServiceTemplate' smart constructor.
data GetServiceTemplate = GetServiceTemplate'
  { -- | The name of the service template that you want to get detailed data for.
    GetServiceTemplate -> Text
name :: Prelude.Text
  }
  deriving (GetServiceTemplate -> GetServiceTemplate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetServiceTemplate -> GetServiceTemplate -> Bool
$c/= :: GetServiceTemplate -> GetServiceTemplate -> Bool
== :: GetServiceTemplate -> GetServiceTemplate -> Bool
$c== :: GetServiceTemplate -> GetServiceTemplate -> Bool
Prelude.Eq, ReadPrec [GetServiceTemplate]
ReadPrec GetServiceTemplate
Int -> ReadS GetServiceTemplate
ReadS [GetServiceTemplate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetServiceTemplate]
$creadListPrec :: ReadPrec [GetServiceTemplate]
readPrec :: ReadPrec GetServiceTemplate
$creadPrec :: ReadPrec GetServiceTemplate
readList :: ReadS [GetServiceTemplate]
$creadList :: ReadS [GetServiceTemplate]
readsPrec :: Int -> ReadS GetServiceTemplate
$creadsPrec :: Int -> ReadS GetServiceTemplate
Prelude.Read, Int -> GetServiceTemplate -> ShowS
[GetServiceTemplate] -> ShowS
GetServiceTemplate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetServiceTemplate] -> ShowS
$cshowList :: [GetServiceTemplate] -> ShowS
show :: GetServiceTemplate -> String
$cshow :: GetServiceTemplate -> String
showsPrec :: Int -> GetServiceTemplate -> ShowS
$cshowsPrec :: Int -> GetServiceTemplate -> ShowS
Prelude.Show, forall x. Rep GetServiceTemplate x -> GetServiceTemplate
forall x. GetServiceTemplate -> Rep GetServiceTemplate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetServiceTemplate x -> GetServiceTemplate
$cfrom :: forall x. GetServiceTemplate -> Rep GetServiceTemplate x
Prelude.Generic)

-- |
-- Create a value of 'GetServiceTemplate' 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', 'getServiceTemplate_name' - The name of the service template that you want to get detailed data for.
newGetServiceTemplate ::
  -- | 'name'
  Prelude.Text ->
  GetServiceTemplate
newGetServiceTemplate :: Text -> GetServiceTemplate
newGetServiceTemplate Text
pName_ =
  GetServiceTemplate' {$sel:name:GetServiceTemplate' :: Text
name = Text
pName_}

-- | The name of the service template that you want to get detailed data for.
getServiceTemplate_name :: Lens.Lens' GetServiceTemplate Prelude.Text
getServiceTemplate_name :: Lens' GetServiceTemplate Text
getServiceTemplate_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceTemplate' {Text
name :: Text
$sel:name:GetServiceTemplate' :: GetServiceTemplate -> Text
name} -> Text
name) (\s :: GetServiceTemplate
s@GetServiceTemplate' {} Text
a -> GetServiceTemplate
s {$sel:name:GetServiceTemplate' :: Text
name = Text
a} :: GetServiceTemplate)

instance Core.AWSRequest GetServiceTemplate where
  type
    AWSResponse GetServiceTemplate =
      GetServiceTemplateResponse
  request :: (Service -> Service)
-> GetServiceTemplate -> Request GetServiceTemplate
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 GetServiceTemplate
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetServiceTemplate)))
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 ->
          Int -> ServiceTemplate -> GetServiceTemplateResponse
GetServiceTemplateResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"serviceTemplate")
      )

instance Prelude.Hashable GetServiceTemplate where
  hashWithSalt :: Int -> GetServiceTemplate -> Int
hashWithSalt Int
_salt GetServiceTemplate' {Text
name :: Text
$sel:name:GetServiceTemplate' :: GetServiceTemplate -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders GetServiceTemplate where
  toHeaders :: GetServiceTemplate -> 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
"AwsProton20200720.GetServiceTemplate" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetServiceTemplate where
  toJSON :: GetServiceTemplate -> Value
toJSON GetServiceTemplate' {Text
name :: Text
$sel:name:GetServiceTemplate' :: GetServiceTemplate -> 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 GetServiceTemplate where
  toPath :: GetServiceTemplate -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetServiceTemplateResponse' smart constructor.
data GetServiceTemplateResponse = GetServiceTemplateResponse'
  { -- | The response's http status code.
    GetServiceTemplateResponse -> Int
httpStatus :: Prelude.Int,
    -- | The detailed data of the requested service template.
    GetServiceTemplateResponse -> ServiceTemplate
serviceTemplate :: ServiceTemplate
  }
  deriving (GetServiceTemplateResponse -> GetServiceTemplateResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetServiceTemplateResponse -> GetServiceTemplateResponse -> Bool
$c/= :: GetServiceTemplateResponse -> GetServiceTemplateResponse -> Bool
== :: GetServiceTemplateResponse -> GetServiceTemplateResponse -> Bool
$c== :: GetServiceTemplateResponse -> GetServiceTemplateResponse -> Bool
Prelude.Eq, Int -> GetServiceTemplateResponse -> ShowS
[GetServiceTemplateResponse] -> ShowS
GetServiceTemplateResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetServiceTemplateResponse] -> ShowS
$cshowList :: [GetServiceTemplateResponse] -> ShowS
show :: GetServiceTemplateResponse -> String
$cshow :: GetServiceTemplateResponse -> String
showsPrec :: Int -> GetServiceTemplateResponse -> ShowS
$cshowsPrec :: Int -> GetServiceTemplateResponse -> ShowS
Prelude.Show, forall x.
Rep GetServiceTemplateResponse x -> GetServiceTemplateResponse
forall x.
GetServiceTemplateResponse -> Rep GetServiceTemplateResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetServiceTemplateResponse x -> GetServiceTemplateResponse
$cfrom :: forall x.
GetServiceTemplateResponse -> Rep GetServiceTemplateResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetServiceTemplateResponse' 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:
--
-- 'httpStatus', 'getServiceTemplateResponse_httpStatus' - The response's http status code.
--
-- 'serviceTemplate', 'getServiceTemplateResponse_serviceTemplate' - The detailed data of the requested service template.
newGetServiceTemplateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'serviceTemplate'
  ServiceTemplate ->
  GetServiceTemplateResponse
newGetServiceTemplateResponse :: Int -> ServiceTemplate -> GetServiceTemplateResponse
newGetServiceTemplateResponse
  Int
pHttpStatus_
  ServiceTemplate
pServiceTemplate_ =
    GetServiceTemplateResponse'
      { $sel:httpStatus:GetServiceTemplateResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:serviceTemplate:GetServiceTemplateResponse' :: ServiceTemplate
serviceTemplate = ServiceTemplate
pServiceTemplate_
      }

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

-- | The detailed data of the requested service template.
getServiceTemplateResponse_serviceTemplate :: Lens.Lens' GetServiceTemplateResponse ServiceTemplate
getServiceTemplateResponse_serviceTemplate :: Lens' GetServiceTemplateResponse ServiceTemplate
getServiceTemplateResponse_serviceTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceTemplateResponse' {ServiceTemplate
serviceTemplate :: ServiceTemplate
$sel:serviceTemplate:GetServiceTemplateResponse' :: GetServiceTemplateResponse -> ServiceTemplate
serviceTemplate} -> ServiceTemplate
serviceTemplate) (\s :: GetServiceTemplateResponse
s@GetServiceTemplateResponse' {} ServiceTemplate
a -> GetServiceTemplateResponse
s {$sel:serviceTemplate:GetServiceTemplateResponse' :: ServiceTemplate
serviceTemplate = ServiceTemplate
a} :: GetServiceTemplateResponse)

instance Prelude.NFData GetServiceTemplateResponse where
  rnf :: GetServiceTemplateResponse -> ()
rnf GetServiceTemplateResponse' {Int
ServiceTemplate
serviceTemplate :: ServiceTemplate
httpStatus :: Int
$sel:serviceTemplate:GetServiceTemplateResponse' :: GetServiceTemplateResponse -> ServiceTemplate
$sel:httpStatus:GetServiceTemplateResponse' :: GetServiceTemplateResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ServiceTemplate
serviceTemplate