{-# 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.MigrationHubReFactorSpaces.GetService
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets an Amazon Web Services Migration Hub Refactor Spaces service.
module Amazonka.MigrationHubReFactorSpaces.GetService
  ( -- * Creating a Request
    GetService (..),
    newGetService,

    -- * Request Lenses
    getService_applicationIdentifier,
    getService_environmentIdentifier,
    getService_serviceIdentifier,

    -- * Destructuring the Response
    GetServiceResponse (..),
    newGetServiceResponse,

    -- * Response Lenses
    getServiceResponse_applicationId,
    getServiceResponse_arn,
    getServiceResponse_createdByAccountId,
    getServiceResponse_createdTime,
    getServiceResponse_description,
    getServiceResponse_endpointType,
    getServiceResponse_environmentId,
    getServiceResponse_error,
    getServiceResponse_lambdaEndpoint,
    getServiceResponse_lastUpdatedTime,
    getServiceResponse_name,
    getServiceResponse_ownerAccountId,
    getServiceResponse_serviceId,
    getServiceResponse_state,
    getServiceResponse_tags,
    getServiceResponse_urlEndpoint,
    getServiceResponse_vpcId,
    getServiceResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetService' smart constructor.
data GetService = GetService'
  { -- | The ID of the application.
    GetService -> Text
applicationIdentifier :: Prelude.Text,
    -- | The ID of the environment.
    GetService -> Text
environmentIdentifier :: Prelude.Text,
    -- | The ID of the service.
    GetService -> Text
serviceIdentifier :: Prelude.Text
  }
  deriving (GetService -> GetService -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetService -> GetService -> Bool
$c/= :: GetService -> GetService -> Bool
== :: GetService -> GetService -> Bool
$c== :: GetService -> GetService -> Bool
Prelude.Eq, ReadPrec [GetService]
ReadPrec GetService
Int -> ReadS GetService
ReadS [GetService]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetService]
$creadListPrec :: ReadPrec [GetService]
readPrec :: ReadPrec GetService
$creadPrec :: ReadPrec GetService
readList :: ReadS [GetService]
$creadList :: ReadS [GetService]
readsPrec :: Int -> ReadS GetService
$creadsPrec :: Int -> ReadS GetService
Prelude.Read, Int -> GetService -> ShowS
[GetService] -> ShowS
GetService -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetService] -> ShowS
$cshowList :: [GetService] -> ShowS
show :: GetService -> String
$cshow :: GetService -> String
showsPrec :: Int -> GetService -> ShowS
$cshowsPrec :: Int -> GetService -> ShowS
Prelude.Show, forall x. Rep GetService x -> GetService
forall x. GetService -> Rep GetService x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetService x -> GetService
$cfrom :: forall x. GetService -> Rep GetService x
Prelude.Generic)

-- |
-- Create a value of 'GetService' 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:
--
-- 'applicationIdentifier', 'getService_applicationIdentifier' - The ID of the application.
--
-- 'environmentIdentifier', 'getService_environmentIdentifier' - The ID of the environment.
--
-- 'serviceIdentifier', 'getService_serviceIdentifier' - The ID of the service.
newGetService ::
  -- | 'applicationIdentifier'
  Prelude.Text ->
  -- | 'environmentIdentifier'
  Prelude.Text ->
  -- | 'serviceIdentifier'
  Prelude.Text ->
  GetService
newGetService :: Text -> Text -> Text -> GetService
newGetService
  Text
pApplicationIdentifier_
  Text
pEnvironmentIdentifier_
  Text
pServiceIdentifier_ =
    GetService'
      { $sel:applicationIdentifier:GetService' :: Text
applicationIdentifier =
          Text
pApplicationIdentifier_,
        $sel:environmentIdentifier:GetService' :: Text
environmentIdentifier = Text
pEnvironmentIdentifier_,
        $sel:serviceIdentifier:GetService' :: Text
serviceIdentifier = Text
pServiceIdentifier_
      }

-- | The ID of the application.
getService_applicationIdentifier :: Lens.Lens' GetService Prelude.Text
getService_applicationIdentifier :: Lens' GetService Text
getService_applicationIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetService' {Text
applicationIdentifier :: Text
$sel:applicationIdentifier:GetService' :: GetService -> Text
applicationIdentifier} -> Text
applicationIdentifier) (\s :: GetService
s@GetService' {} Text
a -> GetService
s {$sel:applicationIdentifier:GetService' :: Text
applicationIdentifier = Text
a} :: GetService)

-- | The ID of the environment.
getService_environmentIdentifier :: Lens.Lens' GetService Prelude.Text
getService_environmentIdentifier :: Lens' GetService Text
getService_environmentIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetService' {Text
environmentIdentifier :: Text
$sel:environmentIdentifier:GetService' :: GetService -> Text
environmentIdentifier} -> Text
environmentIdentifier) (\s :: GetService
s@GetService' {} Text
a -> GetService
s {$sel:environmentIdentifier:GetService' :: Text
environmentIdentifier = Text
a} :: GetService)

-- | The ID of the service.
getService_serviceIdentifier :: Lens.Lens' GetService Prelude.Text
getService_serviceIdentifier :: Lens' GetService Text
getService_serviceIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetService' {Text
serviceIdentifier :: Text
$sel:serviceIdentifier:GetService' :: GetService -> Text
serviceIdentifier} -> Text
serviceIdentifier) (\s :: GetService
s@GetService' {} Text
a -> GetService
s {$sel:serviceIdentifier:GetService' :: Text
serviceIdentifier = Text
a} :: GetService)

instance Core.AWSRequest GetService where
  type AWSResponse GetService = GetServiceResponse
  request :: (Service -> Service) -> GetService -> Request GetService
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 GetService
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetService)))
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 Text
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe ServiceEndpointType
-> Maybe Text
-> Maybe ErrorResponse
-> Maybe LambdaEndpointConfig
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ServiceState
-> Maybe (Sensitive (HashMap Text Text))
-> Maybe UrlEndpointConfig
-> Maybe Text
-> Int
-> GetServiceResponse
GetServiceResponse'
            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
"ApplicationId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreatedByAccountId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreatedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"EndpointType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"EnvironmentId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Error")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LambdaEndpoint")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LastUpdatedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"OwnerAccountId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ServiceId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"State")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"UrlEndpoint")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"VpcId")
            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 GetService where
  hashWithSalt :: Int -> GetService -> Int
hashWithSalt Int
_salt GetService' {Text
serviceIdentifier :: Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:serviceIdentifier:GetService' :: GetService -> Text
$sel:environmentIdentifier:GetService' :: GetService -> Text
$sel:applicationIdentifier:GetService' :: GetService -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceIdentifier

instance Prelude.NFData GetService where
  rnf :: GetService -> ()
rnf GetService' {Text
serviceIdentifier :: Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:serviceIdentifier:GetService' :: GetService -> Text
$sel:environmentIdentifier:GetService' :: GetService -> Text
$sel:applicationIdentifier:GetService' :: GetService -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
environmentIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serviceIdentifier

instance Data.ToHeaders GetService where
  toHeaders :: GetService -> 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 GetService where
  toPath :: GetService -> ByteString
toPath GetService' {Text
serviceIdentifier :: Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:serviceIdentifier:GetService' :: GetService -> Text
$sel:environmentIdentifier:GetService' :: GetService -> Text
$sel:applicationIdentifier:GetService' :: GetService -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/environments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
environmentIdentifier,
        ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationIdentifier,
        ByteString
"/services/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
serviceIdentifier
      ]

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

-- | /See:/ 'newGetServiceResponse' smart constructor.
data GetServiceResponse = GetServiceResponse'
  { -- | The ID of the application.
    GetServiceResponse -> Maybe Text
applicationId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the service.
    GetServiceResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID of the service creator.
    GetServiceResponse -> Maybe Text
createdByAccountId :: Prelude.Maybe Prelude.Text,
    -- | The timestamp of when the service is created.
    GetServiceResponse -> Maybe POSIX
createdTime :: Prelude.Maybe Data.POSIX,
    -- | The description of the service.
    GetServiceResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The endpoint type of the service.
    GetServiceResponse -> Maybe ServiceEndpointType
endpointType :: Prelude.Maybe ServiceEndpointType,
    -- | The unique identifier of the environment.
    GetServiceResponse -> Maybe Text
environmentId :: Prelude.Maybe Prelude.Text,
    -- | Any error associated with the service resource.
    GetServiceResponse -> Maybe ErrorResponse
error :: Prelude.Maybe ErrorResponse,
    -- | The configuration for the Lambda endpoint type.
    --
    -- The __Arn__ is the Amazon Resource Name (ARN) of the Lambda function
    -- associated with this service.
    GetServiceResponse -> Maybe LambdaEndpointConfig
lambdaEndpoint :: Prelude.Maybe LambdaEndpointConfig,
    -- | A timestamp that indicates when the service was last updated.
    GetServiceResponse -> Maybe POSIX
lastUpdatedTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the service.
    GetServiceResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID of the service owner.
    GetServiceResponse -> Maybe Text
ownerAccountId :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier of the service.
    GetServiceResponse -> Maybe Text
serviceId :: Prelude.Maybe Prelude.Text,
    -- | The current state of the service.
    GetServiceResponse -> Maybe ServiceState
state :: Prelude.Maybe ServiceState,
    -- | The tags assigned to the service. A tag is a label that you assign to an
    -- Amazon Web Services resource. Each tag consists of a key-value pair.
    GetServiceResponse -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | The configuration for the URL endpoint type.
    --
    -- The __Url__ isthe URL of the endpoint type.
    --
    -- The __HealthUrl__ is the health check URL of the endpoint type.
    GetServiceResponse -> Maybe UrlEndpointConfig
urlEndpoint :: Prelude.Maybe UrlEndpointConfig,
    -- | The ID of the virtual private cloud (VPC).
    GetServiceResponse -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetServiceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetServiceResponse -> GetServiceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetServiceResponse -> GetServiceResponse -> Bool
$c/= :: GetServiceResponse -> GetServiceResponse -> Bool
== :: GetServiceResponse -> GetServiceResponse -> Bool
$c== :: GetServiceResponse -> GetServiceResponse -> Bool
Prelude.Eq, Int -> GetServiceResponse -> ShowS
[GetServiceResponse] -> ShowS
GetServiceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetServiceResponse] -> ShowS
$cshowList :: [GetServiceResponse] -> ShowS
show :: GetServiceResponse -> String
$cshow :: GetServiceResponse -> String
showsPrec :: Int -> GetServiceResponse -> ShowS
$cshowsPrec :: Int -> GetServiceResponse -> ShowS
Prelude.Show, forall x. Rep GetServiceResponse x -> GetServiceResponse
forall x. GetServiceResponse -> Rep GetServiceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetServiceResponse x -> GetServiceResponse
$cfrom :: forall x. GetServiceResponse -> Rep GetServiceResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetServiceResponse' 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:
--
-- 'applicationId', 'getServiceResponse_applicationId' - The ID of the application.
--
-- 'arn', 'getServiceResponse_arn' - The Amazon Resource Name (ARN) of the service.
--
-- 'createdByAccountId', 'getServiceResponse_createdByAccountId' - The Amazon Web Services account ID of the service creator.
--
-- 'createdTime', 'getServiceResponse_createdTime' - The timestamp of when the service is created.
--
-- 'description', 'getServiceResponse_description' - The description of the service.
--
-- 'endpointType', 'getServiceResponse_endpointType' - The endpoint type of the service.
--
-- 'environmentId', 'getServiceResponse_environmentId' - The unique identifier of the environment.
--
-- 'error', 'getServiceResponse_error' - Any error associated with the service resource.
--
-- 'lambdaEndpoint', 'getServiceResponse_lambdaEndpoint' - The configuration for the Lambda endpoint type.
--
-- The __Arn__ is the Amazon Resource Name (ARN) of the Lambda function
-- associated with this service.
--
-- 'lastUpdatedTime', 'getServiceResponse_lastUpdatedTime' - A timestamp that indicates when the service was last updated.
--
-- 'name', 'getServiceResponse_name' - The name of the service.
--
-- 'ownerAccountId', 'getServiceResponse_ownerAccountId' - The Amazon Web Services account ID of the service owner.
--
-- 'serviceId', 'getServiceResponse_serviceId' - The unique identifier of the service.
--
-- 'state', 'getServiceResponse_state' - The current state of the service.
--
-- 'tags', 'getServiceResponse_tags' - The tags assigned to the service. A tag is a label that you assign to an
-- Amazon Web Services resource. Each tag consists of a key-value pair.
--
-- 'urlEndpoint', 'getServiceResponse_urlEndpoint' - The configuration for the URL endpoint type.
--
-- The __Url__ isthe URL of the endpoint type.
--
-- The __HealthUrl__ is the health check URL of the endpoint type.
--
-- 'vpcId', 'getServiceResponse_vpcId' - The ID of the virtual private cloud (VPC).
--
-- 'httpStatus', 'getServiceResponse_httpStatus' - The response's http status code.
newGetServiceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetServiceResponse
newGetServiceResponse :: Int -> GetServiceResponse
newGetServiceResponse Int
pHttpStatus_ =
  GetServiceResponse'
    { $sel:applicationId:GetServiceResponse' :: Maybe Text
applicationId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:arn:GetServiceResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdByAccountId:GetServiceResponse' :: Maybe Text
createdByAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:createdTime:GetServiceResponse' :: Maybe POSIX
createdTime = forall a. Maybe a
Prelude.Nothing,
      $sel:description:GetServiceResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointType:GetServiceResponse' :: Maybe ServiceEndpointType
endpointType = forall a. Maybe a
Prelude.Nothing,
      $sel:environmentId:GetServiceResponse' :: Maybe Text
environmentId = forall a. Maybe a
Prelude.Nothing,
      $sel:error:GetServiceResponse' :: Maybe ErrorResponse
error = forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaEndpoint:GetServiceResponse' :: Maybe LambdaEndpointConfig
lambdaEndpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedTime:GetServiceResponse' :: Maybe POSIX
lastUpdatedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetServiceResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerAccountId:GetServiceResponse' :: Maybe Text
ownerAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceId:GetServiceResponse' :: Maybe Text
serviceId = forall a. Maybe a
Prelude.Nothing,
      $sel:state:GetServiceResponse' :: Maybe ServiceState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetServiceResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:urlEndpoint:GetServiceResponse' :: Maybe UrlEndpointConfig
urlEndpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:GetServiceResponse' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetServiceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the application.
getServiceResponse_applicationId :: Lens.Lens' GetServiceResponse (Prelude.Maybe Prelude.Text)
getServiceResponse_applicationId :: Lens' GetServiceResponse (Maybe Text)
getServiceResponse_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe Text
applicationId :: Maybe Text
$sel:applicationId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
applicationId} -> Maybe Text
applicationId) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe Text
a -> GetServiceResponse
s {$sel:applicationId:GetServiceResponse' :: Maybe Text
applicationId = Maybe Text
a} :: GetServiceResponse)

-- | The Amazon Resource Name (ARN) of the service.
getServiceResponse_arn :: Lens.Lens' GetServiceResponse (Prelude.Maybe Prelude.Text)
getServiceResponse_arn :: Lens' GetServiceResponse (Maybe Text)
getServiceResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:GetServiceResponse' :: GetServiceResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe Text
a -> GetServiceResponse
s {$sel:arn:GetServiceResponse' :: Maybe Text
arn = Maybe Text
a} :: GetServiceResponse)

-- | The Amazon Web Services account ID of the service creator.
getServiceResponse_createdByAccountId :: Lens.Lens' GetServiceResponse (Prelude.Maybe Prelude.Text)
getServiceResponse_createdByAccountId :: Lens' GetServiceResponse (Maybe Text)
getServiceResponse_createdByAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe Text
createdByAccountId :: Maybe Text
$sel:createdByAccountId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
createdByAccountId} -> Maybe Text
createdByAccountId) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe Text
a -> GetServiceResponse
s {$sel:createdByAccountId:GetServiceResponse' :: Maybe Text
createdByAccountId = Maybe Text
a} :: GetServiceResponse)

-- | The timestamp of when the service is created.
getServiceResponse_createdTime :: Lens.Lens' GetServiceResponse (Prelude.Maybe Prelude.UTCTime)
getServiceResponse_createdTime :: Lens' GetServiceResponse (Maybe UTCTime)
getServiceResponse_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe POSIX
createdTime :: Maybe POSIX
$sel:createdTime:GetServiceResponse' :: GetServiceResponse -> Maybe POSIX
createdTime} -> Maybe POSIX
createdTime) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe POSIX
a -> GetServiceResponse
s {$sel:createdTime:GetServiceResponse' :: Maybe POSIX
createdTime = Maybe POSIX
a} :: GetServiceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The description of the service.
getServiceResponse_description :: Lens.Lens' GetServiceResponse (Prelude.Maybe Prelude.Text)
getServiceResponse_description :: Lens' GetServiceResponse (Maybe Text)
getServiceResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetServiceResponse' :: GetServiceResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe Text
a -> GetServiceResponse
s {$sel:description:GetServiceResponse' :: Maybe Text
description = Maybe Text
a} :: GetServiceResponse)

-- | The endpoint type of the service.
getServiceResponse_endpointType :: Lens.Lens' GetServiceResponse (Prelude.Maybe ServiceEndpointType)
getServiceResponse_endpointType :: Lens' GetServiceResponse (Maybe ServiceEndpointType)
getServiceResponse_endpointType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe ServiceEndpointType
endpointType :: Maybe ServiceEndpointType
$sel:endpointType:GetServiceResponse' :: GetServiceResponse -> Maybe ServiceEndpointType
endpointType} -> Maybe ServiceEndpointType
endpointType) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe ServiceEndpointType
a -> GetServiceResponse
s {$sel:endpointType:GetServiceResponse' :: Maybe ServiceEndpointType
endpointType = Maybe ServiceEndpointType
a} :: GetServiceResponse)

-- | The unique identifier of the environment.
getServiceResponse_environmentId :: Lens.Lens' GetServiceResponse (Prelude.Maybe Prelude.Text)
getServiceResponse_environmentId :: Lens' GetServiceResponse (Maybe Text)
getServiceResponse_environmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe Text
environmentId :: Maybe Text
$sel:environmentId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
environmentId} -> Maybe Text
environmentId) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe Text
a -> GetServiceResponse
s {$sel:environmentId:GetServiceResponse' :: Maybe Text
environmentId = Maybe Text
a} :: GetServiceResponse)

-- | Any error associated with the service resource.
getServiceResponse_error :: Lens.Lens' GetServiceResponse (Prelude.Maybe ErrorResponse)
getServiceResponse_error :: Lens' GetServiceResponse (Maybe ErrorResponse)
getServiceResponse_error = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe ErrorResponse
error :: Maybe ErrorResponse
$sel:error:GetServiceResponse' :: GetServiceResponse -> Maybe ErrorResponse
error} -> Maybe ErrorResponse
error) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe ErrorResponse
a -> GetServiceResponse
s {$sel:error:GetServiceResponse' :: Maybe ErrorResponse
error = Maybe ErrorResponse
a} :: GetServiceResponse)

-- | The configuration for the Lambda endpoint type.
--
-- The __Arn__ is the Amazon Resource Name (ARN) of the Lambda function
-- associated with this service.
getServiceResponse_lambdaEndpoint :: Lens.Lens' GetServiceResponse (Prelude.Maybe LambdaEndpointConfig)
getServiceResponse_lambdaEndpoint :: Lens' GetServiceResponse (Maybe LambdaEndpointConfig)
getServiceResponse_lambdaEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe LambdaEndpointConfig
lambdaEndpoint :: Maybe LambdaEndpointConfig
$sel:lambdaEndpoint:GetServiceResponse' :: GetServiceResponse -> Maybe LambdaEndpointConfig
lambdaEndpoint} -> Maybe LambdaEndpointConfig
lambdaEndpoint) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe LambdaEndpointConfig
a -> GetServiceResponse
s {$sel:lambdaEndpoint:GetServiceResponse' :: Maybe LambdaEndpointConfig
lambdaEndpoint = Maybe LambdaEndpointConfig
a} :: GetServiceResponse)

-- | A timestamp that indicates when the service was last updated.
getServiceResponse_lastUpdatedTime :: Lens.Lens' GetServiceResponse (Prelude.Maybe Prelude.UTCTime)
getServiceResponse_lastUpdatedTime :: Lens' GetServiceResponse (Maybe UTCTime)
getServiceResponse_lastUpdatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe POSIX
lastUpdatedTime :: Maybe POSIX
$sel:lastUpdatedTime:GetServiceResponse' :: GetServiceResponse -> Maybe POSIX
lastUpdatedTime} -> Maybe POSIX
lastUpdatedTime) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe POSIX
a -> GetServiceResponse
s {$sel:lastUpdatedTime:GetServiceResponse' :: Maybe POSIX
lastUpdatedTime = Maybe POSIX
a} :: GetServiceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

-- | The Amazon Web Services account ID of the service owner.
getServiceResponse_ownerAccountId :: Lens.Lens' GetServiceResponse (Prelude.Maybe Prelude.Text)
getServiceResponse_ownerAccountId :: Lens' GetServiceResponse (Maybe Text)
getServiceResponse_ownerAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe Text
ownerAccountId :: Maybe Text
$sel:ownerAccountId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
ownerAccountId} -> Maybe Text
ownerAccountId) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe Text
a -> GetServiceResponse
s {$sel:ownerAccountId:GetServiceResponse' :: Maybe Text
ownerAccountId = Maybe Text
a} :: GetServiceResponse)

-- | The unique identifier of the service.
getServiceResponse_serviceId :: Lens.Lens' GetServiceResponse (Prelude.Maybe Prelude.Text)
getServiceResponse_serviceId :: Lens' GetServiceResponse (Maybe Text)
getServiceResponse_serviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe Text
serviceId :: Maybe Text
$sel:serviceId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
serviceId} -> Maybe Text
serviceId) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe Text
a -> GetServiceResponse
s {$sel:serviceId:GetServiceResponse' :: Maybe Text
serviceId = Maybe Text
a} :: GetServiceResponse)

-- | The current state of the service.
getServiceResponse_state :: Lens.Lens' GetServiceResponse (Prelude.Maybe ServiceState)
getServiceResponse_state :: Lens' GetServiceResponse (Maybe ServiceState)
getServiceResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe ServiceState
state :: Maybe ServiceState
$sel:state:GetServiceResponse' :: GetServiceResponse -> Maybe ServiceState
state} -> Maybe ServiceState
state) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe ServiceState
a -> GetServiceResponse
s {$sel:state:GetServiceResponse' :: Maybe ServiceState
state = Maybe ServiceState
a} :: GetServiceResponse)

-- | The tags assigned to the service. A tag is a label that you assign to an
-- Amazon Web Services resource. Each tag consists of a key-value pair.
getServiceResponse_tags :: Lens.Lens' GetServiceResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getServiceResponse_tags :: Lens' GetServiceResponse (Maybe (HashMap Text Text))
getServiceResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:GetServiceResponse' :: GetServiceResponse -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe (Sensitive (HashMap Text Text))
a -> GetServiceResponse
s {$sel:tags:GetServiceResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: GetServiceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping (forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | The configuration for the URL endpoint type.
--
-- The __Url__ isthe URL of the endpoint type.
--
-- The __HealthUrl__ is the health check URL of the endpoint type.
getServiceResponse_urlEndpoint :: Lens.Lens' GetServiceResponse (Prelude.Maybe UrlEndpointConfig)
getServiceResponse_urlEndpoint :: Lens' GetServiceResponse (Maybe UrlEndpointConfig)
getServiceResponse_urlEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe UrlEndpointConfig
urlEndpoint :: Maybe UrlEndpointConfig
$sel:urlEndpoint:GetServiceResponse' :: GetServiceResponse -> Maybe UrlEndpointConfig
urlEndpoint} -> Maybe UrlEndpointConfig
urlEndpoint) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe UrlEndpointConfig
a -> GetServiceResponse
s {$sel:urlEndpoint:GetServiceResponse' :: Maybe UrlEndpointConfig
urlEndpoint = Maybe UrlEndpointConfig
a} :: GetServiceResponse)

-- | The ID of the virtual private cloud (VPC).
getServiceResponse_vpcId :: Lens.Lens' GetServiceResponse (Prelude.Maybe Prelude.Text)
getServiceResponse_vpcId :: Lens' GetServiceResponse (Maybe Text)
getServiceResponse_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetServiceResponse' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: GetServiceResponse
s@GetServiceResponse' {} Maybe Text
a -> GetServiceResponse
s {$sel:vpcId:GetServiceResponse' :: Maybe Text
vpcId = Maybe Text
a} :: GetServiceResponse)

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

instance Prelude.NFData GetServiceResponse where
  rnf :: GetServiceResponse -> ()
rnf GetServiceResponse' {Int
Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe POSIX
Maybe ErrorResponse
Maybe LambdaEndpointConfig
Maybe ServiceEndpointType
Maybe ServiceState
Maybe UrlEndpointConfig
httpStatus :: Int
vpcId :: Maybe Text
urlEndpoint :: Maybe UrlEndpointConfig
tags :: Maybe (Sensitive (HashMap Text Text))
state :: Maybe ServiceState
serviceId :: Maybe Text
ownerAccountId :: Maybe Text
name :: Maybe Text
lastUpdatedTime :: Maybe POSIX
lambdaEndpoint :: Maybe LambdaEndpointConfig
error :: Maybe ErrorResponse
environmentId :: Maybe Text
endpointType :: Maybe ServiceEndpointType
description :: Maybe Text
createdTime :: Maybe POSIX
createdByAccountId :: Maybe Text
arn :: Maybe Text
applicationId :: Maybe Text
$sel:httpStatus:GetServiceResponse' :: GetServiceResponse -> Int
$sel:vpcId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
$sel:urlEndpoint:GetServiceResponse' :: GetServiceResponse -> Maybe UrlEndpointConfig
$sel:tags:GetServiceResponse' :: GetServiceResponse -> Maybe (Sensitive (HashMap Text Text))
$sel:state:GetServiceResponse' :: GetServiceResponse -> Maybe ServiceState
$sel:serviceId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
$sel:ownerAccountId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
$sel:name:GetServiceResponse' :: GetServiceResponse -> Maybe Text
$sel:lastUpdatedTime:GetServiceResponse' :: GetServiceResponse -> Maybe POSIX
$sel:lambdaEndpoint:GetServiceResponse' :: GetServiceResponse -> Maybe LambdaEndpointConfig
$sel:error:GetServiceResponse' :: GetServiceResponse -> Maybe ErrorResponse
$sel:environmentId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
$sel:endpointType:GetServiceResponse' :: GetServiceResponse -> Maybe ServiceEndpointType
$sel:description:GetServiceResponse' :: GetServiceResponse -> Maybe Text
$sel:createdTime:GetServiceResponse' :: GetServiceResponse -> Maybe POSIX
$sel:createdByAccountId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
$sel:arn:GetServiceResponse' :: GetServiceResponse -> Maybe Text
$sel:applicationId:GetServiceResponse' :: GetServiceResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
createdByAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ServiceEndpointType
endpointType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
environmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ErrorResponse
error
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LambdaEndpointConfig
lambdaEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ownerAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serviceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ServiceState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text Text))
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UrlEndpointConfig
urlEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus