{-# 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.StopPipe
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stop an existing pipe.
module Amazonka.Pipes.StopPipe
  ( -- * Creating a Request
    StopPipe (..),
    newStopPipe,

    -- * Request Lenses
    stopPipe_name,

    -- * Destructuring the Response
    StopPipeResponse (..),
    newStopPipeResponse,

    -- * Response Lenses
    stopPipeResponse_arn,
    stopPipeResponse_creationTime,
    stopPipeResponse_currentState,
    stopPipeResponse_desiredState,
    stopPipeResponse_lastModifiedTime,
    stopPipeResponse_name,
    stopPipeResponse_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:/ 'newStopPipe' smart constructor.
data StopPipe = StopPipe'
  { -- | The name of the pipe.
    StopPipe -> Text
name :: Prelude.Text
  }
  deriving (StopPipe -> StopPipe -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopPipe -> StopPipe -> Bool
$c/= :: StopPipe -> StopPipe -> Bool
== :: StopPipe -> StopPipe -> Bool
$c== :: StopPipe -> StopPipe -> Bool
Prelude.Eq, ReadPrec [StopPipe]
ReadPrec StopPipe
Int -> ReadS StopPipe
ReadS [StopPipe]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopPipe]
$creadListPrec :: ReadPrec [StopPipe]
readPrec :: ReadPrec StopPipe
$creadPrec :: ReadPrec StopPipe
readList :: ReadS [StopPipe]
$creadList :: ReadS [StopPipe]
readsPrec :: Int -> ReadS StopPipe
$creadsPrec :: Int -> ReadS StopPipe
Prelude.Read, Int -> StopPipe -> ShowS
[StopPipe] -> ShowS
StopPipe -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopPipe] -> ShowS
$cshowList :: [StopPipe] -> ShowS
show :: StopPipe -> String
$cshow :: StopPipe -> String
showsPrec :: Int -> StopPipe -> ShowS
$cshowsPrec :: Int -> StopPipe -> ShowS
Prelude.Show, forall x. Rep StopPipe x -> StopPipe
forall x. StopPipe -> Rep StopPipe x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopPipe x -> StopPipe
$cfrom :: forall x. StopPipe -> Rep StopPipe x
Prelude.Generic)

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

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

instance Core.AWSRequest StopPipe where
  type AWSResponse StopPipe = StopPipeResponse
  request :: (Service -> Service) -> StopPipe -> Request StopPipe
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 StopPipe
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StopPipe)))
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 RequestedPipeState
-> Maybe POSIX
-> Maybe Text
-> Int
-> StopPipeResponse
StopPipeResponse'
            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 StopPipe where
  hashWithSalt :: Int -> StopPipe -> Int
hashWithSalt Int
_salt StopPipe' {Text
name :: Text
$sel:name:StopPipe' :: StopPipe -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders StopPipe where
  toHeaders :: StopPipe -> 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.ToJSON StopPipe where
  toJSON :: StopPipe -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath StopPipe where
  toPath :: StopPipe -> ByteString
toPath StopPipe' {Text
name :: Text
$sel:name:StopPipe' :: StopPipe -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/pipes/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name, ByteString
"/stop"]

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

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

-- |
-- Create a value of 'StopPipeResponse' 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', 'stopPipeResponse_arn' - The ARN of the pipe.
--
-- 'creationTime', 'stopPipeResponse_creationTime' - The time the pipe was created.
--
-- 'currentState', 'stopPipeResponse_currentState' - The state the pipe is in.
--
-- 'desiredState', 'stopPipeResponse_desiredState' - The state the pipe should be in.
--
-- 'lastModifiedTime', 'stopPipeResponse_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', 'stopPipeResponse_name' - The name of the pipe.
--
-- 'httpStatus', 'stopPipeResponse_httpStatus' - The response's http status code.
newStopPipeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopPipeResponse
newStopPipeResponse :: Int -> StopPipeResponse
newStopPipeResponse Int
pHttpStatus_ =
  StopPipeResponse'
    { $sel:arn:StopPipeResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:StopPipeResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:currentState:StopPipeResponse' :: Maybe PipeState
currentState = forall a. Maybe a
Prelude.Nothing,
      $sel:desiredState:StopPipeResponse' :: Maybe RequestedPipeState
desiredState = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:StopPipeResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:StopPipeResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StopPipeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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

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

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

instance Prelude.NFData StopPipeResponse where
  rnf :: StopPipeResponse -> ()
rnf StopPipeResponse' {Int
Maybe Text
Maybe POSIX
Maybe PipeState
Maybe RequestedPipeState
httpStatus :: Int
name :: Maybe Text
lastModifiedTime :: Maybe POSIX
desiredState :: Maybe RequestedPipeState
currentState :: Maybe PipeState
creationTime :: Maybe POSIX
arn :: Maybe Text
$sel:httpStatus:StopPipeResponse' :: StopPipeResponse -> Int
$sel:name:StopPipeResponse' :: StopPipeResponse -> Maybe Text
$sel:lastModifiedTime:StopPipeResponse' :: StopPipeResponse -> Maybe POSIX
$sel:desiredState:StopPipeResponse' :: StopPipeResponse -> Maybe RequestedPipeState
$sel:currentState:StopPipeResponse' :: StopPipeResponse -> Maybe PipeState
$sel:creationTime:StopPipeResponse' :: StopPipeResponse -> Maybe POSIX
$sel:arn:StopPipeResponse' :: StopPipeResponse -> 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 RequestedPipeState
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