{-# 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.MediaLive.StopMultiplex
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops a running multiplex. If the multiplex isn\'t running, this action
-- has no effect.
module Amazonka.MediaLive.StopMultiplex
  ( -- * Creating a Request
    StopMultiplex (..),
    newStopMultiplex,

    -- * Request Lenses
    stopMultiplex_multiplexId,

    -- * Destructuring the Response
    StopMultiplexResponse (..),
    newStopMultiplexResponse,

    -- * Response Lenses
    stopMultiplexResponse_arn,
    stopMultiplexResponse_availabilityZones,
    stopMultiplexResponse_destinations,
    stopMultiplexResponse_id,
    stopMultiplexResponse_multiplexSettings,
    stopMultiplexResponse_name,
    stopMultiplexResponse_pipelinesRunningCount,
    stopMultiplexResponse_programCount,
    stopMultiplexResponse_state,
    stopMultiplexResponse_tags,
    stopMultiplexResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'StopMultiplex' 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:
--
-- 'multiplexId', 'stopMultiplex_multiplexId' - The ID of the multiplex.
newStopMultiplex ::
  -- | 'multiplexId'
  Prelude.Text ->
  StopMultiplex
newStopMultiplex :: Text -> StopMultiplex
newStopMultiplex Text
pMultiplexId_ =
  StopMultiplex' {$sel:multiplexId:StopMultiplex' :: Text
multiplexId = Text
pMultiplexId_}

-- | The ID of the multiplex.
stopMultiplex_multiplexId :: Lens.Lens' StopMultiplex Prelude.Text
stopMultiplex_multiplexId :: Lens' StopMultiplex Text
stopMultiplex_multiplexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopMultiplex' {Text
multiplexId :: Text
$sel:multiplexId:StopMultiplex' :: StopMultiplex -> Text
multiplexId} -> Text
multiplexId) (\s :: StopMultiplex
s@StopMultiplex' {} Text
a -> StopMultiplex
s {$sel:multiplexId:StopMultiplex' :: Text
multiplexId = Text
a} :: StopMultiplex)

instance Core.AWSRequest StopMultiplex where
  type
    AWSResponse StopMultiplex =
      StopMultiplexResponse
  request :: (Service -> Service) -> StopMultiplex -> Request StopMultiplex
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 StopMultiplex
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StopMultiplex)))
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 [MultiplexOutputDestination]
-> Maybe Text
-> Maybe MultiplexSettings
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe MultiplexState
-> Maybe (HashMap Text Text)
-> Int
-> StopMultiplexResponse
StopMultiplexResponse'
            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
"availabilityZones"
                            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
"destinations" 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
"id")
            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
"multiplexSettings")
            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
"pipelinesRunningCount")
            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
"programCount")
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

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

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

instance Data.ToPath StopMultiplex where
  toPath :: StopMultiplex -> ByteString
toPath StopMultiplex' {Text
multiplexId :: Text
$sel:multiplexId:StopMultiplex' :: StopMultiplex -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/prod/multiplexes/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
multiplexId,
        ByteString
"/stop"
      ]

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

-- | Placeholder documentation for StopMultiplexResponse
--
-- /See:/ 'newStopMultiplexResponse' smart constructor.
data StopMultiplexResponse = StopMultiplexResponse'
  { -- | The unique arn of the multiplex.
    StopMultiplexResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | A list of availability zones for the multiplex.
    StopMultiplexResponse -> Maybe [Text]
availabilityZones :: Prelude.Maybe [Prelude.Text],
    -- | A list of the multiplex output destinations.
    StopMultiplexResponse -> Maybe [MultiplexOutputDestination]
destinations :: Prelude.Maybe [MultiplexOutputDestination],
    -- | The unique id of the multiplex.
    StopMultiplexResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | Configuration for a multiplex event.
    StopMultiplexResponse -> Maybe MultiplexSettings
multiplexSettings :: Prelude.Maybe MultiplexSettings,
    -- | The name of the multiplex.
    StopMultiplexResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The number of currently healthy pipelines.
    StopMultiplexResponse -> Maybe Int
pipelinesRunningCount :: Prelude.Maybe Prelude.Int,
    -- | The number of programs in the multiplex.
    StopMultiplexResponse -> Maybe Int
programCount :: Prelude.Maybe Prelude.Int,
    -- | The current state of the multiplex.
    StopMultiplexResponse -> Maybe MultiplexState
state :: Prelude.Maybe MultiplexState,
    -- | A collection of key-value pairs.
    StopMultiplexResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    StopMultiplexResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StopMultiplexResponse -> StopMultiplexResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopMultiplexResponse -> StopMultiplexResponse -> Bool
$c/= :: StopMultiplexResponse -> StopMultiplexResponse -> Bool
== :: StopMultiplexResponse -> StopMultiplexResponse -> Bool
$c== :: StopMultiplexResponse -> StopMultiplexResponse -> Bool
Prelude.Eq, ReadPrec [StopMultiplexResponse]
ReadPrec StopMultiplexResponse
Int -> ReadS StopMultiplexResponse
ReadS [StopMultiplexResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopMultiplexResponse]
$creadListPrec :: ReadPrec [StopMultiplexResponse]
readPrec :: ReadPrec StopMultiplexResponse
$creadPrec :: ReadPrec StopMultiplexResponse
readList :: ReadS [StopMultiplexResponse]
$creadList :: ReadS [StopMultiplexResponse]
readsPrec :: Int -> ReadS StopMultiplexResponse
$creadsPrec :: Int -> ReadS StopMultiplexResponse
Prelude.Read, Int -> StopMultiplexResponse -> ShowS
[StopMultiplexResponse] -> ShowS
StopMultiplexResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopMultiplexResponse] -> ShowS
$cshowList :: [StopMultiplexResponse] -> ShowS
show :: StopMultiplexResponse -> String
$cshow :: StopMultiplexResponse -> String
showsPrec :: Int -> StopMultiplexResponse -> ShowS
$cshowsPrec :: Int -> StopMultiplexResponse -> ShowS
Prelude.Show, forall x. Rep StopMultiplexResponse x -> StopMultiplexResponse
forall x. StopMultiplexResponse -> Rep StopMultiplexResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopMultiplexResponse x -> StopMultiplexResponse
$cfrom :: forall x. StopMultiplexResponse -> Rep StopMultiplexResponse x
Prelude.Generic)

-- |
-- Create a value of 'StopMultiplexResponse' 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', 'stopMultiplexResponse_arn' - The unique arn of the multiplex.
--
-- 'availabilityZones', 'stopMultiplexResponse_availabilityZones' - A list of availability zones for the multiplex.
--
-- 'destinations', 'stopMultiplexResponse_destinations' - A list of the multiplex output destinations.
--
-- 'id', 'stopMultiplexResponse_id' - The unique id of the multiplex.
--
-- 'multiplexSettings', 'stopMultiplexResponse_multiplexSettings' - Configuration for a multiplex event.
--
-- 'name', 'stopMultiplexResponse_name' - The name of the multiplex.
--
-- 'pipelinesRunningCount', 'stopMultiplexResponse_pipelinesRunningCount' - The number of currently healthy pipelines.
--
-- 'programCount', 'stopMultiplexResponse_programCount' - The number of programs in the multiplex.
--
-- 'state', 'stopMultiplexResponse_state' - The current state of the multiplex.
--
-- 'tags', 'stopMultiplexResponse_tags' - A collection of key-value pairs.
--
-- 'httpStatus', 'stopMultiplexResponse_httpStatus' - The response's http status code.
newStopMultiplexResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopMultiplexResponse
newStopMultiplexResponse :: Int -> StopMultiplexResponse
newStopMultiplexResponse Int
pHttpStatus_ =
  StopMultiplexResponse'
    { $sel:arn:StopMultiplexResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:availabilityZones:StopMultiplexResponse' :: Maybe [Text]
availabilityZones = forall a. Maybe a
Prelude.Nothing,
      $sel:destinations:StopMultiplexResponse' :: Maybe [MultiplexOutputDestination]
destinations = forall a. Maybe a
Prelude.Nothing,
      $sel:id:StopMultiplexResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:multiplexSettings:StopMultiplexResponse' :: Maybe MultiplexSettings
multiplexSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:name:StopMultiplexResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:pipelinesRunningCount:StopMultiplexResponse' :: Maybe Int
pipelinesRunningCount = forall a. Maybe a
Prelude.Nothing,
      $sel:programCount:StopMultiplexResponse' :: Maybe Int
programCount = forall a. Maybe a
Prelude.Nothing,
      $sel:state:StopMultiplexResponse' :: Maybe MultiplexState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:StopMultiplexResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StopMultiplexResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The unique arn of the multiplex.
stopMultiplexResponse_arn :: Lens.Lens' StopMultiplexResponse (Prelude.Maybe Prelude.Text)
stopMultiplexResponse_arn :: Lens' StopMultiplexResponse (Maybe Text)
stopMultiplexResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopMultiplexResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: StopMultiplexResponse
s@StopMultiplexResponse' {} Maybe Text
a -> StopMultiplexResponse
s {$sel:arn:StopMultiplexResponse' :: Maybe Text
arn = Maybe Text
a} :: StopMultiplexResponse)

-- | A list of availability zones for the multiplex.
stopMultiplexResponse_availabilityZones :: Lens.Lens' StopMultiplexResponse (Prelude.Maybe [Prelude.Text])
stopMultiplexResponse_availabilityZones :: Lens' StopMultiplexResponse (Maybe [Text])
stopMultiplexResponse_availabilityZones = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopMultiplexResponse' {Maybe [Text]
availabilityZones :: Maybe [Text]
$sel:availabilityZones:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe [Text]
availabilityZones} -> Maybe [Text]
availabilityZones) (\s :: StopMultiplexResponse
s@StopMultiplexResponse' {} Maybe [Text]
a -> StopMultiplexResponse
s {$sel:availabilityZones:StopMultiplexResponse' :: Maybe [Text]
availabilityZones = Maybe [Text]
a} :: StopMultiplexResponse) 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 list of the multiplex output destinations.
stopMultiplexResponse_destinations :: Lens.Lens' StopMultiplexResponse (Prelude.Maybe [MultiplexOutputDestination])
stopMultiplexResponse_destinations :: Lens' StopMultiplexResponse (Maybe [MultiplexOutputDestination])
stopMultiplexResponse_destinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopMultiplexResponse' {Maybe [MultiplexOutputDestination]
destinations :: Maybe [MultiplexOutputDestination]
$sel:destinations:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe [MultiplexOutputDestination]
destinations} -> Maybe [MultiplexOutputDestination]
destinations) (\s :: StopMultiplexResponse
s@StopMultiplexResponse' {} Maybe [MultiplexOutputDestination]
a -> StopMultiplexResponse
s {$sel:destinations:StopMultiplexResponse' :: Maybe [MultiplexOutputDestination]
destinations = Maybe [MultiplexOutputDestination]
a} :: StopMultiplexResponse) 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

-- | The unique id of the multiplex.
stopMultiplexResponse_id :: Lens.Lens' StopMultiplexResponse (Prelude.Maybe Prelude.Text)
stopMultiplexResponse_id :: Lens' StopMultiplexResponse (Maybe Text)
stopMultiplexResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopMultiplexResponse' {Maybe Text
id :: Maybe Text
$sel:id:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: StopMultiplexResponse
s@StopMultiplexResponse' {} Maybe Text
a -> StopMultiplexResponse
s {$sel:id:StopMultiplexResponse' :: Maybe Text
id = Maybe Text
a} :: StopMultiplexResponse)

-- | Configuration for a multiplex event.
stopMultiplexResponse_multiplexSettings :: Lens.Lens' StopMultiplexResponse (Prelude.Maybe MultiplexSettings)
stopMultiplexResponse_multiplexSettings :: Lens' StopMultiplexResponse (Maybe MultiplexSettings)
stopMultiplexResponse_multiplexSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopMultiplexResponse' {Maybe MultiplexSettings
multiplexSettings :: Maybe MultiplexSettings
$sel:multiplexSettings:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe MultiplexSettings
multiplexSettings} -> Maybe MultiplexSettings
multiplexSettings) (\s :: StopMultiplexResponse
s@StopMultiplexResponse' {} Maybe MultiplexSettings
a -> StopMultiplexResponse
s {$sel:multiplexSettings:StopMultiplexResponse' :: Maybe MultiplexSettings
multiplexSettings = Maybe MultiplexSettings
a} :: StopMultiplexResponse)

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

-- | The number of currently healthy pipelines.
stopMultiplexResponse_pipelinesRunningCount :: Lens.Lens' StopMultiplexResponse (Prelude.Maybe Prelude.Int)
stopMultiplexResponse_pipelinesRunningCount :: Lens' StopMultiplexResponse (Maybe Int)
stopMultiplexResponse_pipelinesRunningCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopMultiplexResponse' {Maybe Int
pipelinesRunningCount :: Maybe Int
$sel:pipelinesRunningCount:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe Int
pipelinesRunningCount} -> Maybe Int
pipelinesRunningCount) (\s :: StopMultiplexResponse
s@StopMultiplexResponse' {} Maybe Int
a -> StopMultiplexResponse
s {$sel:pipelinesRunningCount:StopMultiplexResponse' :: Maybe Int
pipelinesRunningCount = Maybe Int
a} :: StopMultiplexResponse)

-- | The number of programs in the multiplex.
stopMultiplexResponse_programCount :: Lens.Lens' StopMultiplexResponse (Prelude.Maybe Prelude.Int)
stopMultiplexResponse_programCount :: Lens' StopMultiplexResponse (Maybe Int)
stopMultiplexResponse_programCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopMultiplexResponse' {Maybe Int
programCount :: Maybe Int
$sel:programCount:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe Int
programCount} -> Maybe Int
programCount) (\s :: StopMultiplexResponse
s@StopMultiplexResponse' {} Maybe Int
a -> StopMultiplexResponse
s {$sel:programCount:StopMultiplexResponse' :: Maybe Int
programCount = Maybe Int
a} :: StopMultiplexResponse)

-- | The current state of the multiplex.
stopMultiplexResponse_state :: Lens.Lens' StopMultiplexResponse (Prelude.Maybe MultiplexState)
stopMultiplexResponse_state :: Lens' StopMultiplexResponse (Maybe MultiplexState)
stopMultiplexResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopMultiplexResponse' {Maybe MultiplexState
state :: Maybe MultiplexState
$sel:state:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe MultiplexState
state} -> Maybe MultiplexState
state) (\s :: StopMultiplexResponse
s@StopMultiplexResponse' {} Maybe MultiplexState
a -> StopMultiplexResponse
s {$sel:state:StopMultiplexResponse' :: Maybe MultiplexState
state = Maybe MultiplexState
a} :: StopMultiplexResponse)

-- | A collection of key-value pairs.
stopMultiplexResponse_tags :: Lens.Lens' StopMultiplexResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
stopMultiplexResponse_tags :: Lens' StopMultiplexResponse (Maybe (HashMap Text Text))
stopMultiplexResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopMultiplexResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: StopMultiplexResponse
s@StopMultiplexResponse' {} Maybe (HashMap Text Text)
a -> StopMultiplexResponse
s {$sel:tags:StopMultiplexResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: StopMultiplexResponse) 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

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

instance Prelude.NFData StopMultiplexResponse where
  rnf :: StopMultiplexResponse -> ()
rnf StopMultiplexResponse' {Int
Maybe Int
Maybe [Text]
Maybe [MultiplexOutputDestination]
Maybe Text
Maybe (HashMap Text Text)
Maybe MultiplexSettings
Maybe MultiplexState
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
state :: Maybe MultiplexState
programCount :: Maybe Int
pipelinesRunningCount :: Maybe Int
name :: Maybe Text
multiplexSettings :: Maybe MultiplexSettings
id :: Maybe Text
destinations :: Maybe [MultiplexOutputDestination]
availabilityZones :: Maybe [Text]
arn :: Maybe Text
$sel:httpStatus:StopMultiplexResponse' :: StopMultiplexResponse -> Int
$sel:tags:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe (HashMap Text Text)
$sel:state:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe MultiplexState
$sel:programCount:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe Int
$sel:pipelinesRunningCount:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe Int
$sel:name:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe Text
$sel:multiplexSettings:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe MultiplexSettings
$sel:id:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe Text
$sel:destinations:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe [MultiplexOutputDestination]
$sel:availabilityZones:StopMultiplexResponse' :: StopMultiplexResponse -> Maybe [Text]
$sel:arn:StopMultiplexResponse' :: StopMultiplexResponse -> 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 [Text]
availabilityZones
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [MultiplexOutputDestination]
destinations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MultiplexSettings
multiplexSettings
      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 Int
pipelinesRunningCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
programCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MultiplexState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus