{-# 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.Pipes.DeletePipe
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Delete an existing pipe. For more information about pipes, see
-- <https://docs.aws.amazon.com/eventbridge/latest/userguide/eb-pipes.html Amazon EventBridge Pipes>
-- in the Amazon EventBridge User Guide.
module Amazonka.Pipes.DeletePipe
  ( -- * Creating a Request
    DeletePipe (..),
    newDeletePipe,

    -- * Request Lenses
    deletePipe_name,

    -- * Destructuring the Response
    DeletePipeResponse (..),
    newDeletePipeResponse,

    -- * Response Lenses
    deletePipeResponse_arn,
    deletePipeResponse_creationTime,
    deletePipeResponse_currentState,
    deletePipeResponse_desiredState,
    deletePipeResponse_lastModifiedTime,
    deletePipeResponse_name,
    deletePipeResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'DeletePipe' 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', 'deletePipe_name' - The name of the pipe.
newDeletePipe ::
  -- | 'name'
  Prelude.Text ->
  DeletePipe
newDeletePipe :: Text -> DeletePipe
newDeletePipe Text
pName_ = DeletePipe' {$sel:name:DeletePipe' :: Text
name = Text
pName_}

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

instance Core.AWSRequest DeletePipe where
  type AWSResponse DeletePipe = DeletePipeResponse
  request :: (Service -> Service) -> DeletePipe -> Request DeletePipe
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeletePipe
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeletePipe)))
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 POSIX
-> Maybe PipeState
-> Maybe RequestedPipeStateDescribeResponse
-> Maybe POSIX
-> Maybe Text
-> Int
-> DeletePipeResponse
DeletePipeResponse'
            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
"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
"CreationTime")
            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
"CurrentState")
            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
"DesiredState")
            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
"LastModifiedTime")
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

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

instance Data.ToHeaders DeletePipe where
  toHeaders :: DeletePipe -> 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 DeletePipe where
  toPath :: DeletePipe -> ByteString
toPath DeletePipe' {Text
name :: Text
$sel:name:DeletePipe' :: DeletePipe -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/v1/pipes/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

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

-- | /See:/ 'newDeletePipeResponse' smart constructor.
data DeletePipeResponse = DeletePipeResponse'
  { -- | The ARN of the pipe.
    DeletePipeResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The time the pipe was created.
    DeletePipeResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The state the pipe is in.
    DeletePipeResponse -> Maybe PipeState
currentState :: Prelude.Maybe PipeState,
    -- | The state the pipe should be in.
    DeletePipeResponse -> Maybe RequestedPipeStateDescribeResponse
desiredState :: Prelude.Maybe RequestedPipeStateDescribeResponse,
    -- | When the pipe was last updated, in
    -- <https://www.w3.org/TR/NOTE-datetime ISO-8601 format>
    -- (YYYY-MM-DDThh:mm:ss.sTZD).
    DeletePipeResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the pipe.
    DeletePipeResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeletePipeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeletePipeResponse -> DeletePipeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePipeResponse -> DeletePipeResponse -> Bool
$c/= :: DeletePipeResponse -> DeletePipeResponse -> Bool
== :: DeletePipeResponse -> DeletePipeResponse -> Bool
$c== :: DeletePipeResponse -> DeletePipeResponse -> Bool
Prelude.Eq, ReadPrec [DeletePipeResponse]
ReadPrec DeletePipeResponse
Int -> ReadS DeletePipeResponse
ReadS [DeletePipeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePipeResponse]
$creadListPrec :: ReadPrec [DeletePipeResponse]
readPrec :: ReadPrec DeletePipeResponse
$creadPrec :: ReadPrec DeletePipeResponse
readList :: ReadS [DeletePipeResponse]
$creadList :: ReadS [DeletePipeResponse]
readsPrec :: Int -> ReadS DeletePipeResponse
$creadsPrec :: Int -> ReadS DeletePipeResponse
Prelude.Read, Int -> DeletePipeResponse -> ShowS
[DeletePipeResponse] -> ShowS
DeletePipeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePipeResponse] -> ShowS
$cshowList :: [DeletePipeResponse] -> ShowS
show :: DeletePipeResponse -> String
$cshow :: DeletePipeResponse -> String
showsPrec :: Int -> DeletePipeResponse -> ShowS
$cshowsPrec :: Int -> DeletePipeResponse -> ShowS
Prelude.Show, forall x. Rep DeletePipeResponse x -> DeletePipeResponse
forall x. DeletePipeResponse -> Rep DeletePipeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeletePipeResponse x -> DeletePipeResponse
$cfrom :: forall x. DeletePipeResponse -> Rep DeletePipeResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeletePipeResponse' 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:
--
-- 'arn', 'deletePipeResponse_arn' - The ARN of the pipe.
--
-- 'creationTime', 'deletePipeResponse_creationTime' - The time the pipe was created.
--
-- 'currentState', 'deletePipeResponse_currentState' - The state the pipe is in.
--
-- 'desiredState', 'deletePipeResponse_desiredState' - The state the pipe should be in.
--
-- 'lastModifiedTime', 'deletePipeResponse_lastModifiedTime' - When the pipe was last updated, in
-- <https://www.w3.org/TR/NOTE-datetime ISO-8601 format>
-- (YYYY-MM-DDThh:mm:ss.sTZD).
--
-- 'name', 'deletePipeResponse_name' - The name of the pipe.
--
-- 'httpStatus', 'deletePipeResponse_httpStatus' - The response's http status code.
newDeletePipeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeletePipeResponse
newDeletePipeResponse :: Int -> DeletePipeResponse
newDeletePipeResponse Int
pHttpStatus_ =
  DeletePipeResponse'
    { $sel:arn:DeletePipeResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:DeletePipeResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:currentState:DeletePipeResponse' :: Maybe PipeState
currentState = forall a. Maybe a
Prelude.Nothing,
      $sel:desiredState:DeletePipeResponse' :: Maybe RequestedPipeStateDescribeResponse
desiredState = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:DeletePipeResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DeletePipeResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeletePipeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the pipe.
deletePipeResponse_arn :: Lens.Lens' DeletePipeResponse (Prelude.Maybe Prelude.Text)
deletePipeResponse_arn :: Lens' DeletePipeResponse (Maybe Text)
deletePipeResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePipeResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:DeletePipeResponse' :: DeletePipeResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: DeletePipeResponse
s@DeletePipeResponse' {} Maybe Text
a -> DeletePipeResponse
s {$sel:arn:DeletePipeResponse' :: Maybe Text
arn = Maybe Text
a} :: DeletePipeResponse)

-- | The time the pipe was created.
deletePipeResponse_creationTime :: Lens.Lens' DeletePipeResponse (Prelude.Maybe Prelude.UTCTime)
deletePipeResponse_creationTime :: Lens' DeletePipeResponse (Maybe UTCTime)
deletePipeResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePipeResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DeletePipeResponse' :: DeletePipeResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DeletePipeResponse
s@DeletePipeResponse' {} Maybe POSIX
a -> DeletePipeResponse
s {$sel:creationTime:DeletePipeResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DeletePipeResponse) 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 state the pipe is in.
deletePipeResponse_currentState :: Lens.Lens' DeletePipeResponse (Prelude.Maybe PipeState)
deletePipeResponse_currentState :: Lens' DeletePipeResponse (Maybe PipeState)
deletePipeResponse_currentState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePipeResponse' {Maybe PipeState
currentState :: Maybe PipeState
$sel:currentState:DeletePipeResponse' :: DeletePipeResponse -> Maybe PipeState
currentState} -> Maybe PipeState
currentState) (\s :: DeletePipeResponse
s@DeletePipeResponse' {} Maybe PipeState
a -> DeletePipeResponse
s {$sel:currentState:DeletePipeResponse' :: Maybe PipeState
currentState = Maybe PipeState
a} :: DeletePipeResponse)

-- | The state the pipe should be in.
deletePipeResponse_desiredState :: Lens.Lens' DeletePipeResponse (Prelude.Maybe RequestedPipeStateDescribeResponse)
deletePipeResponse_desiredState :: Lens' DeletePipeResponse (Maybe RequestedPipeStateDescribeResponse)
deletePipeResponse_desiredState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePipeResponse' {Maybe RequestedPipeStateDescribeResponse
desiredState :: Maybe RequestedPipeStateDescribeResponse
$sel:desiredState:DeletePipeResponse' :: DeletePipeResponse -> Maybe RequestedPipeStateDescribeResponse
desiredState} -> Maybe RequestedPipeStateDescribeResponse
desiredState) (\s :: DeletePipeResponse
s@DeletePipeResponse' {} Maybe RequestedPipeStateDescribeResponse
a -> DeletePipeResponse
s {$sel:desiredState:DeletePipeResponse' :: Maybe RequestedPipeStateDescribeResponse
desiredState = Maybe RequestedPipeStateDescribeResponse
a} :: DeletePipeResponse)

-- | When the pipe was last updated, in
-- <https://www.w3.org/TR/NOTE-datetime ISO-8601 format>
-- (YYYY-MM-DDThh:mm:ss.sTZD).
deletePipeResponse_lastModifiedTime :: Lens.Lens' DeletePipeResponse (Prelude.Maybe Prelude.UTCTime)
deletePipeResponse_lastModifiedTime :: Lens' DeletePipeResponse (Maybe UTCTime)
deletePipeResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePipeResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:DeletePipeResponse' :: DeletePipeResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: DeletePipeResponse
s@DeletePipeResponse' {} Maybe POSIX
a -> DeletePipeResponse
s {$sel:lastModifiedTime:DeletePipeResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: DeletePipeResponse) 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 pipe.
deletePipeResponse_name :: Lens.Lens' DeletePipeResponse (Prelude.Maybe Prelude.Text)
deletePipeResponse_name :: Lens' DeletePipeResponse (Maybe Text)
deletePipeResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePipeResponse' {Maybe Text
name :: Maybe Text
$sel:name:DeletePipeResponse' :: DeletePipeResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: DeletePipeResponse
s@DeletePipeResponse' {} Maybe Text
a -> DeletePipeResponse
s {$sel:name:DeletePipeResponse' :: Maybe Text
name = Maybe Text
a} :: DeletePipeResponse)

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

instance Prelude.NFData DeletePipeResponse where
  rnf :: DeletePipeResponse -> ()
rnf DeletePipeResponse' {Int
Maybe Text
Maybe POSIX
Maybe PipeState
Maybe RequestedPipeStateDescribeResponse
httpStatus :: Int
name :: Maybe Text
lastModifiedTime :: Maybe POSIX
desiredState :: Maybe RequestedPipeStateDescribeResponse
currentState :: Maybe PipeState
creationTime :: Maybe POSIX
arn :: Maybe Text
$sel:httpStatus:DeletePipeResponse' :: DeletePipeResponse -> Int
$sel:name:DeletePipeResponse' :: DeletePipeResponse -> Maybe Text
$sel:lastModifiedTime:DeletePipeResponse' :: DeletePipeResponse -> Maybe POSIX
$sel:desiredState:DeletePipeResponse' :: DeletePipeResponse -> Maybe RequestedPipeStateDescribeResponse
$sel:currentState:DeletePipeResponse' :: DeletePipeResponse -> Maybe PipeState
$sel:creationTime:DeletePipeResponse' :: DeletePipeResponse -> Maybe POSIX
$sel:arn:DeletePipeResponse' :: DeletePipeResponse -> Maybe Text
..} =
    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 POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PipeState
currentState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RequestedPipeStateDescribeResponse
desiredState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTime
      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 Int
httpStatus