{-# 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.GetBlueprintRuns
-- 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 blueprint runs for a specified blueprint.
module Amazonka.Glue.GetBlueprintRuns
  ( -- * Creating a Request
    GetBlueprintRuns (..),
    newGetBlueprintRuns,

    -- * Request Lenses
    getBlueprintRuns_maxResults,
    getBlueprintRuns_nextToken,
    getBlueprintRuns_blueprintName,

    -- * Destructuring the Response
    GetBlueprintRunsResponse (..),
    newGetBlueprintRunsResponse,

    -- * Response Lenses
    getBlueprintRunsResponse_blueprintRuns,
    getBlueprintRunsResponse_nextToken,
    getBlueprintRunsResponse_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:/ 'newGetBlueprintRuns' smart constructor.
data GetBlueprintRuns = GetBlueprintRuns'
  { -- | The maximum size of a list to return.
    GetBlueprintRuns -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A continuation token, if this is a continuation request.
    GetBlueprintRuns -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the blueprint.
    GetBlueprintRuns -> Text
blueprintName :: Prelude.Text
  }
  deriving (GetBlueprintRuns -> GetBlueprintRuns -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBlueprintRuns -> GetBlueprintRuns -> Bool
$c/= :: GetBlueprintRuns -> GetBlueprintRuns -> Bool
== :: GetBlueprintRuns -> GetBlueprintRuns -> Bool
$c== :: GetBlueprintRuns -> GetBlueprintRuns -> Bool
Prelude.Eq, ReadPrec [GetBlueprintRuns]
ReadPrec GetBlueprintRuns
Int -> ReadS GetBlueprintRuns
ReadS [GetBlueprintRuns]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBlueprintRuns]
$creadListPrec :: ReadPrec [GetBlueprintRuns]
readPrec :: ReadPrec GetBlueprintRuns
$creadPrec :: ReadPrec GetBlueprintRuns
readList :: ReadS [GetBlueprintRuns]
$creadList :: ReadS [GetBlueprintRuns]
readsPrec :: Int -> ReadS GetBlueprintRuns
$creadsPrec :: Int -> ReadS GetBlueprintRuns
Prelude.Read, Int -> GetBlueprintRuns -> ShowS
[GetBlueprintRuns] -> ShowS
GetBlueprintRuns -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBlueprintRuns] -> ShowS
$cshowList :: [GetBlueprintRuns] -> ShowS
show :: GetBlueprintRuns -> String
$cshow :: GetBlueprintRuns -> String
showsPrec :: Int -> GetBlueprintRuns -> ShowS
$cshowsPrec :: Int -> GetBlueprintRuns -> ShowS
Prelude.Show, forall x. Rep GetBlueprintRuns x -> GetBlueprintRuns
forall x. GetBlueprintRuns -> Rep GetBlueprintRuns x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBlueprintRuns x -> GetBlueprintRuns
$cfrom :: forall x. GetBlueprintRuns -> Rep GetBlueprintRuns x
Prelude.Generic)

-- |
-- Create a value of 'GetBlueprintRuns' 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:
--
-- 'maxResults', 'getBlueprintRuns_maxResults' - The maximum size of a list to return.
--
-- 'nextToken', 'getBlueprintRuns_nextToken' - A continuation token, if this is a continuation request.
--
-- 'blueprintName', 'getBlueprintRuns_blueprintName' - The name of the blueprint.
newGetBlueprintRuns ::
  -- | 'blueprintName'
  Prelude.Text ->
  GetBlueprintRuns
newGetBlueprintRuns :: Text -> GetBlueprintRuns
newGetBlueprintRuns Text
pBlueprintName_ =
  GetBlueprintRuns'
    { $sel:maxResults:GetBlueprintRuns' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetBlueprintRuns' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:blueprintName:GetBlueprintRuns' :: Text
blueprintName = Text
pBlueprintName_
    }

-- | The maximum size of a list to return.
getBlueprintRuns_maxResults :: Lens.Lens' GetBlueprintRuns (Prelude.Maybe Prelude.Natural)
getBlueprintRuns_maxResults :: Lens' GetBlueprintRuns (Maybe Natural)
getBlueprintRuns_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprintRuns' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetBlueprintRuns' :: GetBlueprintRuns -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetBlueprintRuns
s@GetBlueprintRuns' {} Maybe Natural
a -> GetBlueprintRuns
s {$sel:maxResults:GetBlueprintRuns' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetBlueprintRuns)

-- | A continuation token, if this is a continuation request.
getBlueprintRuns_nextToken :: Lens.Lens' GetBlueprintRuns (Prelude.Maybe Prelude.Text)
getBlueprintRuns_nextToken :: Lens' GetBlueprintRuns (Maybe Text)
getBlueprintRuns_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprintRuns' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetBlueprintRuns' :: GetBlueprintRuns -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetBlueprintRuns
s@GetBlueprintRuns' {} Maybe Text
a -> GetBlueprintRuns
s {$sel:nextToken:GetBlueprintRuns' :: Maybe Text
nextToken = Maybe Text
a} :: GetBlueprintRuns)

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

instance Core.AWSRequest GetBlueprintRuns where
  type
    AWSResponse GetBlueprintRuns =
      GetBlueprintRunsResponse
  request :: (Service -> Service)
-> GetBlueprintRuns -> Request GetBlueprintRuns
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 GetBlueprintRuns
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetBlueprintRuns)))
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 [BlueprintRun]
-> Maybe Text -> Int -> GetBlueprintRunsResponse
GetBlueprintRunsResponse'
            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
"BlueprintRuns" 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
"NextToken")
            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 GetBlueprintRuns where
  hashWithSalt :: Int -> GetBlueprintRuns -> Int
hashWithSalt Int
_salt GetBlueprintRuns' {Maybe Natural
Maybe Text
Text
blueprintName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:blueprintName:GetBlueprintRuns' :: GetBlueprintRuns -> Text
$sel:nextToken:GetBlueprintRuns' :: GetBlueprintRuns -> Maybe Text
$sel:maxResults:GetBlueprintRuns' :: GetBlueprintRuns -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
blueprintName

instance Prelude.NFData GetBlueprintRuns where
  rnf :: GetBlueprintRuns -> ()
rnf GetBlueprintRuns' {Maybe Natural
Maybe Text
Text
blueprintName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:blueprintName:GetBlueprintRuns' :: GetBlueprintRuns -> Text
$sel:nextToken:GetBlueprintRuns' :: GetBlueprintRuns -> Maybe Text
$sel:maxResults:GetBlueprintRuns' :: GetBlueprintRuns -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
blueprintName

instance Data.ToHeaders GetBlueprintRuns where
  toHeaders :: GetBlueprintRuns -> 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.GetBlueprintRuns" :: 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 GetBlueprintRuns where
  toJSON :: GetBlueprintRuns -> Value
toJSON GetBlueprintRuns' {Maybe Natural
Maybe Text
Text
blueprintName :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:blueprintName:GetBlueprintRuns' :: GetBlueprintRuns -> Text
$sel:nextToken:GetBlueprintRuns' :: GetBlueprintRuns -> Maybe Text
$sel:maxResults:GetBlueprintRuns' :: GetBlueprintRuns -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxResults" 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 Natural
maxResults,
            (Key
"NextToken" 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 Text
nextToken,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"BlueprintName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
blueprintName)
          ]
      )

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

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

-- | /See:/ 'newGetBlueprintRunsResponse' smart constructor.
data GetBlueprintRunsResponse = GetBlueprintRunsResponse'
  { -- | Returns a list of @BlueprintRun@ objects.
    GetBlueprintRunsResponse -> Maybe [BlueprintRun]
blueprintRuns :: Prelude.Maybe [BlueprintRun],
    -- | A continuation token, if not all blueprint runs have been returned.
    GetBlueprintRunsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetBlueprintRunsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBlueprintRunsResponse -> GetBlueprintRunsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBlueprintRunsResponse -> GetBlueprintRunsResponse -> Bool
$c/= :: GetBlueprintRunsResponse -> GetBlueprintRunsResponse -> Bool
== :: GetBlueprintRunsResponse -> GetBlueprintRunsResponse -> Bool
$c== :: GetBlueprintRunsResponse -> GetBlueprintRunsResponse -> Bool
Prelude.Eq, ReadPrec [GetBlueprintRunsResponse]
ReadPrec GetBlueprintRunsResponse
Int -> ReadS GetBlueprintRunsResponse
ReadS [GetBlueprintRunsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBlueprintRunsResponse]
$creadListPrec :: ReadPrec [GetBlueprintRunsResponse]
readPrec :: ReadPrec GetBlueprintRunsResponse
$creadPrec :: ReadPrec GetBlueprintRunsResponse
readList :: ReadS [GetBlueprintRunsResponse]
$creadList :: ReadS [GetBlueprintRunsResponse]
readsPrec :: Int -> ReadS GetBlueprintRunsResponse
$creadsPrec :: Int -> ReadS GetBlueprintRunsResponse
Prelude.Read, Int -> GetBlueprintRunsResponse -> ShowS
[GetBlueprintRunsResponse] -> ShowS
GetBlueprintRunsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBlueprintRunsResponse] -> ShowS
$cshowList :: [GetBlueprintRunsResponse] -> ShowS
show :: GetBlueprintRunsResponse -> String
$cshow :: GetBlueprintRunsResponse -> String
showsPrec :: Int -> GetBlueprintRunsResponse -> ShowS
$cshowsPrec :: Int -> GetBlueprintRunsResponse -> ShowS
Prelude.Show, forall x.
Rep GetBlueprintRunsResponse x -> GetBlueprintRunsResponse
forall x.
GetBlueprintRunsResponse -> Rep GetBlueprintRunsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBlueprintRunsResponse x -> GetBlueprintRunsResponse
$cfrom :: forall x.
GetBlueprintRunsResponse -> Rep GetBlueprintRunsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBlueprintRunsResponse' 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:
--
-- 'blueprintRuns', 'getBlueprintRunsResponse_blueprintRuns' - Returns a list of @BlueprintRun@ objects.
--
-- 'nextToken', 'getBlueprintRunsResponse_nextToken' - A continuation token, if not all blueprint runs have been returned.
--
-- 'httpStatus', 'getBlueprintRunsResponse_httpStatus' - The response's http status code.
newGetBlueprintRunsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBlueprintRunsResponse
newGetBlueprintRunsResponse :: Int -> GetBlueprintRunsResponse
newGetBlueprintRunsResponse Int
pHttpStatus_ =
  GetBlueprintRunsResponse'
    { $sel:blueprintRuns:GetBlueprintRunsResponse' :: Maybe [BlueprintRun]
blueprintRuns =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetBlueprintRunsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBlueprintRunsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns a list of @BlueprintRun@ objects.
getBlueprintRunsResponse_blueprintRuns :: Lens.Lens' GetBlueprintRunsResponse (Prelude.Maybe [BlueprintRun])
getBlueprintRunsResponse_blueprintRuns :: Lens' GetBlueprintRunsResponse (Maybe [BlueprintRun])
getBlueprintRunsResponse_blueprintRuns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprintRunsResponse' {Maybe [BlueprintRun]
blueprintRuns :: Maybe [BlueprintRun]
$sel:blueprintRuns:GetBlueprintRunsResponse' :: GetBlueprintRunsResponse -> Maybe [BlueprintRun]
blueprintRuns} -> Maybe [BlueprintRun]
blueprintRuns) (\s :: GetBlueprintRunsResponse
s@GetBlueprintRunsResponse' {} Maybe [BlueprintRun]
a -> GetBlueprintRunsResponse
s {$sel:blueprintRuns:GetBlueprintRunsResponse' :: Maybe [BlueprintRun]
blueprintRuns = Maybe [BlueprintRun]
a} :: GetBlueprintRunsResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A continuation token, if not all blueprint runs have been returned.
getBlueprintRunsResponse_nextToken :: Lens.Lens' GetBlueprintRunsResponse (Prelude.Maybe Prelude.Text)
getBlueprintRunsResponse_nextToken :: Lens' GetBlueprintRunsResponse (Maybe Text)
getBlueprintRunsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprintRunsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetBlueprintRunsResponse' :: GetBlueprintRunsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetBlueprintRunsResponse
s@GetBlueprintRunsResponse' {} Maybe Text
a -> GetBlueprintRunsResponse
s {$sel:nextToken:GetBlueprintRunsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetBlueprintRunsResponse)

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

instance Prelude.NFData GetBlueprintRunsResponse where
  rnf :: GetBlueprintRunsResponse -> ()
rnf GetBlueprintRunsResponse' {Int
Maybe [BlueprintRun]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
blueprintRuns :: Maybe [BlueprintRun]
$sel:httpStatus:GetBlueprintRunsResponse' :: GetBlueprintRunsResponse -> Int
$sel:nextToken:GetBlueprintRunsResponse' :: GetBlueprintRunsResponse -> Maybe Text
$sel:blueprintRuns:GetBlueprintRunsResponse' :: GetBlueprintRunsResponse -> Maybe [BlueprintRun]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [BlueprintRun]
blueprintRuns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus