{-# 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.AppRunner.DescribeService
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Return a full description of an App Runner service.
module Amazonka.AppRunner.DescribeService
  ( -- * Creating a Request
    DescribeService (..),
    newDescribeService,

    -- * Request Lenses
    describeService_serviceArn,

    -- * Destructuring the Response
    DescribeServiceResponse (..),
    newDescribeServiceResponse,

    -- * Response Lenses
    describeServiceResponse_httpStatus,
    describeServiceResponse_service,
  )
where

import Amazonka.AppRunner.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:/ 'newDescribeService' smart constructor.
data DescribeService = DescribeService'
  { -- | The Amazon Resource Name (ARN) of the App Runner service that you want a
    -- description for.
    DescribeService -> Text
serviceArn :: Prelude.Text
  }
  deriving (DescribeService -> DescribeService -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeService -> DescribeService -> Bool
$c/= :: DescribeService -> DescribeService -> Bool
== :: DescribeService -> DescribeService -> Bool
$c== :: DescribeService -> DescribeService -> Bool
Prelude.Eq, ReadPrec [DescribeService]
ReadPrec DescribeService
Int -> ReadS DescribeService
ReadS [DescribeService]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeService]
$creadListPrec :: ReadPrec [DescribeService]
readPrec :: ReadPrec DescribeService
$creadPrec :: ReadPrec DescribeService
readList :: ReadS [DescribeService]
$creadList :: ReadS [DescribeService]
readsPrec :: Int -> ReadS DescribeService
$creadsPrec :: Int -> ReadS DescribeService
Prelude.Read, Int -> DescribeService -> ShowS
[DescribeService] -> ShowS
DescribeService -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeService] -> ShowS
$cshowList :: [DescribeService] -> ShowS
show :: DescribeService -> String
$cshow :: DescribeService -> String
showsPrec :: Int -> DescribeService -> ShowS
$cshowsPrec :: Int -> DescribeService -> ShowS
Prelude.Show, forall x. Rep DescribeService x -> DescribeService
forall x. DescribeService -> Rep DescribeService x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeService x -> DescribeService
$cfrom :: forall x. DescribeService -> Rep DescribeService x
Prelude.Generic)

-- |
-- Create a value of 'DescribeService' 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:
--
-- 'serviceArn', 'describeService_serviceArn' - The Amazon Resource Name (ARN) of the App Runner service that you want a
-- description for.
newDescribeService ::
  -- | 'serviceArn'
  Prelude.Text ->
  DescribeService
newDescribeService :: Text -> DescribeService
newDescribeService Text
pServiceArn_ =
  DescribeService' {$sel:serviceArn:DescribeService' :: Text
serviceArn = Text
pServiceArn_}

-- | The Amazon Resource Name (ARN) of the App Runner service that you want a
-- description for.
describeService_serviceArn :: Lens.Lens' DescribeService Prelude.Text
describeService_serviceArn :: Lens' DescribeService Text
describeService_serviceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeService' {Text
serviceArn :: Text
$sel:serviceArn:DescribeService' :: DescribeService -> Text
serviceArn} -> Text
serviceArn) (\s :: DescribeService
s@DescribeService' {} Text
a -> DescribeService
s {$sel:serviceArn:DescribeService' :: Text
serviceArn = Text
a} :: DescribeService)

instance Core.AWSRequest DescribeService where
  type
    AWSResponse DescribeService =
      DescribeServiceResponse
  request :: (Service -> Service) -> DescribeService -> Request DescribeService
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 DescribeService
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeService)))
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 -> Service -> DescribeServiceResponse
DescribeServiceResponse'
            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
"Service")
      )

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

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

instance Data.ToHeaders DescribeService where
  toHeaders :: DescribeService -> 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
"AppRunner.DescribeService" :: 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 DescribeService where
  toJSON :: DescribeService -> Value
toJSON DescribeService' {Text
serviceArn :: Text
$sel:serviceArn:DescribeService' :: DescribeService -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"ServiceArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serviceArn)]
      )

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

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

-- | /See:/ 'newDescribeServiceResponse' smart constructor.
data DescribeServiceResponse = DescribeServiceResponse'
  { -- | The response's http status code.
    DescribeServiceResponse -> Int
httpStatus :: Prelude.Int,
    -- | A full description of the App Runner service that you specified in this
    -- request.
    DescribeServiceResponse -> Service
service :: Service
  }
  deriving (DescribeServiceResponse -> DescribeServiceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeServiceResponse -> DescribeServiceResponse -> Bool
$c/= :: DescribeServiceResponse -> DescribeServiceResponse -> Bool
== :: DescribeServiceResponse -> DescribeServiceResponse -> Bool
$c== :: DescribeServiceResponse -> DescribeServiceResponse -> Bool
Prelude.Eq, Int -> DescribeServiceResponse -> ShowS
[DescribeServiceResponse] -> ShowS
DescribeServiceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeServiceResponse] -> ShowS
$cshowList :: [DescribeServiceResponse] -> ShowS
show :: DescribeServiceResponse -> String
$cshow :: DescribeServiceResponse -> String
showsPrec :: Int -> DescribeServiceResponse -> ShowS
$cshowsPrec :: Int -> DescribeServiceResponse -> ShowS
Prelude.Show, forall x. Rep DescribeServiceResponse x -> DescribeServiceResponse
forall x. DescribeServiceResponse -> Rep DescribeServiceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeServiceResponse x -> DescribeServiceResponse
$cfrom :: forall x. DescribeServiceResponse -> Rep DescribeServiceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeServiceResponse' 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', 'describeServiceResponse_httpStatus' - The response's http status code.
--
-- 'service', 'describeServiceResponse_service' - A full description of the App Runner service that you specified in this
-- request.
newDescribeServiceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'service'
  Service ->
  DescribeServiceResponse
newDescribeServiceResponse :: Int -> Service -> DescribeServiceResponse
newDescribeServiceResponse Int
pHttpStatus_ Service
pService_ =
  DescribeServiceResponse'
    { $sel:httpStatus:DescribeServiceResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:service:DescribeServiceResponse' :: Service
service = Service
pService_
    }

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

-- | A full description of the App Runner service that you specified in this
-- request.
describeServiceResponse_service :: Lens.Lens' DescribeServiceResponse Service
describeServiceResponse_service :: Lens' DescribeServiceResponse Service
describeServiceResponse_service = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeServiceResponse' {Service
service :: Service
$sel:service:DescribeServiceResponse' :: DescribeServiceResponse -> Service
service} -> Service
service) (\s :: DescribeServiceResponse
s@DescribeServiceResponse' {} Service
a -> DescribeServiceResponse
s {$sel:service:DescribeServiceResponse' :: Service
service = Service
a} :: DescribeServiceResponse)

instance Prelude.NFData DescribeServiceResponse where
  rnf :: DescribeServiceResponse -> ()
rnf DescribeServiceResponse' {Int
Service
service :: Service
httpStatus :: Int
$sel:service:DescribeServiceResponse' :: DescribeServiceResponse -> Service
$sel:httpStatus:DescribeServiceResponse' :: DescribeServiceResponse -> 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 Service
service