{-# 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.StopChannel
-- 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 channel
module Amazonka.MediaLive.StopChannel
  ( -- * Creating a Request
    StopChannel (..),
    newStopChannel,

    -- * Request Lenses
    stopChannel_channelId,

    -- * Destructuring the Response
    StopChannelResponse (..),
    newStopChannelResponse,

    -- * Response Lenses
    stopChannelResponse_arn,
    stopChannelResponse_cdiInputSpecification,
    stopChannelResponse_channelClass,
    stopChannelResponse_destinations,
    stopChannelResponse_egressEndpoints,
    stopChannelResponse_encoderSettings,
    stopChannelResponse_id,
    stopChannelResponse_inputAttachments,
    stopChannelResponse_inputSpecification,
    stopChannelResponse_logLevel,
    stopChannelResponse_maintenance,
    stopChannelResponse_name,
    stopChannelResponse_pipelineDetails,
    stopChannelResponse_pipelinesRunningCount,
    stopChannelResponse_roleArn,
    stopChannelResponse_state,
    stopChannelResponse_tags,
    stopChannelResponse_vpc,
    stopChannelResponse_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 StopChannelRequest
--
-- /See:/ 'newStopChannel' smart constructor.
data StopChannel = StopChannel'
  { -- | A request to stop a running channel
    StopChannel -> Text
channelId :: Prelude.Text
  }
  deriving (StopChannel -> StopChannel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopChannel -> StopChannel -> Bool
$c/= :: StopChannel -> StopChannel -> Bool
== :: StopChannel -> StopChannel -> Bool
$c== :: StopChannel -> StopChannel -> Bool
Prelude.Eq, ReadPrec [StopChannel]
ReadPrec StopChannel
Int -> ReadS StopChannel
ReadS [StopChannel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopChannel]
$creadListPrec :: ReadPrec [StopChannel]
readPrec :: ReadPrec StopChannel
$creadPrec :: ReadPrec StopChannel
readList :: ReadS [StopChannel]
$creadList :: ReadS [StopChannel]
readsPrec :: Int -> ReadS StopChannel
$creadsPrec :: Int -> ReadS StopChannel
Prelude.Read, Int -> StopChannel -> ShowS
[StopChannel] -> ShowS
StopChannel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopChannel] -> ShowS
$cshowList :: [StopChannel] -> ShowS
show :: StopChannel -> String
$cshow :: StopChannel -> String
showsPrec :: Int -> StopChannel -> ShowS
$cshowsPrec :: Int -> StopChannel -> ShowS
Prelude.Show, forall x. Rep StopChannel x -> StopChannel
forall x. StopChannel -> Rep StopChannel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopChannel x -> StopChannel
$cfrom :: forall x. StopChannel -> Rep StopChannel x
Prelude.Generic)

-- |
-- Create a value of 'StopChannel' 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:
--
-- 'channelId', 'stopChannel_channelId' - A request to stop a running channel
newStopChannel ::
  -- | 'channelId'
  Prelude.Text ->
  StopChannel
newStopChannel :: Text -> StopChannel
newStopChannel Text
pChannelId_ =
  StopChannel' {$sel:channelId:StopChannel' :: Text
channelId = Text
pChannelId_}

-- | A request to stop a running channel
stopChannel_channelId :: Lens.Lens' StopChannel Prelude.Text
stopChannel_channelId :: Lens' StopChannel Text
stopChannel_channelId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannel' {Text
channelId :: Text
$sel:channelId:StopChannel' :: StopChannel -> Text
channelId} -> Text
channelId) (\s :: StopChannel
s@StopChannel' {} Text
a -> StopChannel
s {$sel:channelId:StopChannel' :: Text
channelId = Text
a} :: StopChannel)

instance Core.AWSRequest StopChannel where
  type AWSResponse StopChannel = StopChannelResponse
  request :: (Service -> Service) -> StopChannel -> Request StopChannel
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 StopChannel
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StopChannel)))
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 CdiInputSpecification
-> Maybe ChannelClass
-> Maybe [OutputDestination]
-> Maybe [ChannelEgressEndpoint]
-> Maybe EncoderSettings
-> Maybe Text
-> Maybe [InputAttachment]
-> Maybe InputSpecification
-> Maybe LogLevel
-> Maybe MaintenanceStatus
-> Maybe Text
-> Maybe [PipelineDetail]
-> Maybe Int
-> Maybe Text
-> Maybe ChannelState
-> Maybe (HashMap Text Text)
-> Maybe VpcOutputSettingsDescription
-> Int
-> StopChannelResponse
StopChannelResponse'
            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
"cdiInputSpecification")
            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
"channelClass")
            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
"egressEndpoints"
                            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
"encoderSettings")
            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
"inputAttachments"
                            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
"inputSpecification")
            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
"logLevel")
            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
"maintenance")
            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
"pipelineDetails"
                            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
"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
"roleArn")
            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
"vpc")
            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 StopChannel where
  hashWithSalt :: Int -> StopChannel -> Int
hashWithSalt Int
_salt StopChannel' {Text
channelId :: Text
$sel:channelId:StopChannel' :: StopChannel -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
channelId

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

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

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

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

-- | Placeholder documentation for StopChannelResponse
--
-- /See:/ 'newStopChannelResponse' smart constructor.
data StopChannelResponse = StopChannelResponse'
  { -- | The unique arn of the channel.
    StopChannelResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | Specification of CDI inputs for this channel
    StopChannelResponse -> Maybe CdiInputSpecification
cdiInputSpecification :: Prelude.Maybe CdiInputSpecification,
    -- | The class for this channel. STANDARD for a channel with two pipelines or
    -- SINGLE_PIPELINE for a channel with one pipeline.
    StopChannelResponse -> Maybe ChannelClass
channelClass :: Prelude.Maybe ChannelClass,
    -- | A list of destinations of the channel. For UDP outputs, there is one
    -- destination per output. For other types (HLS, for example), there is one
    -- destination per packager.
    StopChannelResponse -> Maybe [OutputDestination]
destinations :: Prelude.Maybe [OutputDestination],
    -- | The endpoints where outgoing connections initiate from
    StopChannelResponse -> Maybe [ChannelEgressEndpoint]
egressEndpoints :: Prelude.Maybe [ChannelEgressEndpoint],
    StopChannelResponse -> Maybe EncoderSettings
encoderSettings :: Prelude.Maybe EncoderSettings,
    -- | The unique id of the channel.
    StopChannelResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | List of input attachments for channel.
    StopChannelResponse -> Maybe [InputAttachment]
inputAttachments :: Prelude.Maybe [InputAttachment],
    -- | Specification of network and file inputs for this channel
    StopChannelResponse -> Maybe InputSpecification
inputSpecification :: Prelude.Maybe InputSpecification,
    -- | The log level being written to CloudWatch Logs.
    StopChannelResponse -> Maybe LogLevel
logLevel :: Prelude.Maybe LogLevel,
    -- | Maintenance settings for this channel.
    StopChannelResponse -> Maybe MaintenanceStatus
maintenance :: Prelude.Maybe MaintenanceStatus,
    -- | The name of the channel. (user-mutable)
    StopChannelResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Runtime details for the pipelines of a running channel.
    StopChannelResponse -> Maybe [PipelineDetail]
pipelineDetails :: Prelude.Maybe [PipelineDetail],
    -- | The number of currently healthy pipelines.
    StopChannelResponse -> Maybe Int
pipelinesRunningCount :: Prelude.Maybe Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the role assumed when running the
    -- Channel.
    StopChannelResponse -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    StopChannelResponse -> Maybe ChannelState
state :: Prelude.Maybe ChannelState,
    -- | A collection of key-value pairs.
    StopChannelResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Settings for VPC output
    StopChannelResponse -> Maybe VpcOutputSettingsDescription
vpc :: Prelude.Maybe VpcOutputSettingsDescription,
    -- | The response's http status code.
    StopChannelResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StopChannelResponse -> StopChannelResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopChannelResponse -> StopChannelResponse -> Bool
$c/= :: StopChannelResponse -> StopChannelResponse -> Bool
== :: StopChannelResponse -> StopChannelResponse -> Bool
$c== :: StopChannelResponse -> StopChannelResponse -> Bool
Prelude.Eq, ReadPrec [StopChannelResponse]
ReadPrec StopChannelResponse
Int -> ReadS StopChannelResponse
ReadS [StopChannelResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopChannelResponse]
$creadListPrec :: ReadPrec [StopChannelResponse]
readPrec :: ReadPrec StopChannelResponse
$creadPrec :: ReadPrec StopChannelResponse
readList :: ReadS [StopChannelResponse]
$creadList :: ReadS [StopChannelResponse]
readsPrec :: Int -> ReadS StopChannelResponse
$creadsPrec :: Int -> ReadS StopChannelResponse
Prelude.Read, Int -> StopChannelResponse -> ShowS
[StopChannelResponse] -> ShowS
StopChannelResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopChannelResponse] -> ShowS
$cshowList :: [StopChannelResponse] -> ShowS
show :: StopChannelResponse -> String
$cshow :: StopChannelResponse -> String
showsPrec :: Int -> StopChannelResponse -> ShowS
$cshowsPrec :: Int -> StopChannelResponse -> ShowS
Prelude.Show, forall x. Rep StopChannelResponse x -> StopChannelResponse
forall x. StopChannelResponse -> Rep StopChannelResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopChannelResponse x -> StopChannelResponse
$cfrom :: forall x. StopChannelResponse -> Rep StopChannelResponse x
Prelude.Generic)

-- |
-- Create a value of 'StopChannelResponse' 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', 'stopChannelResponse_arn' - The unique arn of the channel.
--
-- 'cdiInputSpecification', 'stopChannelResponse_cdiInputSpecification' - Specification of CDI inputs for this channel
--
-- 'channelClass', 'stopChannelResponse_channelClass' - The class for this channel. STANDARD for a channel with two pipelines or
-- SINGLE_PIPELINE for a channel with one pipeline.
--
-- 'destinations', 'stopChannelResponse_destinations' - A list of destinations of the channel. For UDP outputs, there is one
-- destination per output. For other types (HLS, for example), there is one
-- destination per packager.
--
-- 'egressEndpoints', 'stopChannelResponse_egressEndpoints' - The endpoints where outgoing connections initiate from
--
-- 'encoderSettings', 'stopChannelResponse_encoderSettings' - Undocumented member.
--
-- 'id', 'stopChannelResponse_id' - The unique id of the channel.
--
-- 'inputAttachments', 'stopChannelResponse_inputAttachments' - List of input attachments for channel.
--
-- 'inputSpecification', 'stopChannelResponse_inputSpecification' - Specification of network and file inputs for this channel
--
-- 'logLevel', 'stopChannelResponse_logLevel' - The log level being written to CloudWatch Logs.
--
-- 'maintenance', 'stopChannelResponse_maintenance' - Maintenance settings for this channel.
--
-- 'name', 'stopChannelResponse_name' - The name of the channel. (user-mutable)
--
-- 'pipelineDetails', 'stopChannelResponse_pipelineDetails' - Runtime details for the pipelines of a running channel.
--
-- 'pipelinesRunningCount', 'stopChannelResponse_pipelinesRunningCount' - The number of currently healthy pipelines.
--
-- 'roleArn', 'stopChannelResponse_roleArn' - The Amazon Resource Name (ARN) of the role assumed when running the
-- Channel.
--
-- 'state', 'stopChannelResponse_state' - Undocumented member.
--
-- 'tags', 'stopChannelResponse_tags' - A collection of key-value pairs.
--
-- 'vpc', 'stopChannelResponse_vpc' - Settings for VPC output
--
-- 'httpStatus', 'stopChannelResponse_httpStatus' - The response's http status code.
newStopChannelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopChannelResponse
newStopChannelResponse :: Int -> StopChannelResponse
newStopChannelResponse Int
pHttpStatus_ =
  StopChannelResponse'
    { $sel:arn:StopChannelResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:cdiInputSpecification:StopChannelResponse' :: Maybe CdiInputSpecification
cdiInputSpecification = forall a. Maybe a
Prelude.Nothing,
      $sel:channelClass:StopChannelResponse' :: Maybe ChannelClass
channelClass = forall a. Maybe a
Prelude.Nothing,
      $sel:destinations:StopChannelResponse' :: Maybe [OutputDestination]
destinations = forall a. Maybe a
Prelude.Nothing,
      $sel:egressEndpoints:StopChannelResponse' :: Maybe [ChannelEgressEndpoint]
egressEndpoints = forall a. Maybe a
Prelude.Nothing,
      $sel:encoderSettings:StopChannelResponse' :: Maybe EncoderSettings
encoderSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:id:StopChannelResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:inputAttachments:StopChannelResponse' :: Maybe [InputAttachment]
inputAttachments = forall a. Maybe a
Prelude.Nothing,
      $sel:inputSpecification:StopChannelResponse' :: Maybe InputSpecification
inputSpecification = forall a. Maybe a
Prelude.Nothing,
      $sel:logLevel:StopChannelResponse' :: Maybe LogLevel
logLevel = forall a. Maybe a
Prelude.Nothing,
      $sel:maintenance:StopChannelResponse' :: Maybe MaintenanceStatus
maintenance = forall a. Maybe a
Prelude.Nothing,
      $sel:name:StopChannelResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:pipelineDetails:StopChannelResponse' :: Maybe [PipelineDetail]
pipelineDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:pipelinesRunningCount:StopChannelResponse' :: Maybe Int
pipelinesRunningCount = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:StopChannelResponse' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:state:StopChannelResponse' :: Maybe ChannelState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:StopChannelResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:vpc:StopChannelResponse' :: Maybe VpcOutputSettingsDescription
vpc = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StopChannelResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | Specification of CDI inputs for this channel
stopChannelResponse_cdiInputSpecification :: Lens.Lens' StopChannelResponse (Prelude.Maybe CdiInputSpecification)
stopChannelResponse_cdiInputSpecification :: Lens' StopChannelResponse (Maybe CdiInputSpecification)
stopChannelResponse_cdiInputSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe CdiInputSpecification
cdiInputSpecification :: Maybe CdiInputSpecification
$sel:cdiInputSpecification:StopChannelResponse' :: StopChannelResponse -> Maybe CdiInputSpecification
cdiInputSpecification} -> Maybe CdiInputSpecification
cdiInputSpecification) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe CdiInputSpecification
a -> StopChannelResponse
s {$sel:cdiInputSpecification:StopChannelResponse' :: Maybe CdiInputSpecification
cdiInputSpecification = Maybe CdiInputSpecification
a} :: StopChannelResponse)

-- | The class for this channel. STANDARD for a channel with two pipelines or
-- SINGLE_PIPELINE for a channel with one pipeline.
stopChannelResponse_channelClass :: Lens.Lens' StopChannelResponse (Prelude.Maybe ChannelClass)
stopChannelResponse_channelClass :: Lens' StopChannelResponse (Maybe ChannelClass)
stopChannelResponse_channelClass = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe ChannelClass
channelClass :: Maybe ChannelClass
$sel:channelClass:StopChannelResponse' :: StopChannelResponse -> Maybe ChannelClass
channelClass} -> Maybe ChannelClass
channelClass) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe ChannelClass
a -> StopChannelResponse
s {$sel:channelClass:StopChannelResponse' :: Maybe ChannelClass
channelClass = Maybe ChannelClass
a} :: StopChannelResponse)

-- | A list of destinations of the channel. For UDP outputs, there is one
-- destination per output. For other types (HLS, for example), there is one
-- destination per packager.
stopChannelResponse_destinations :: Lens.Lens' StopChannelResponse (Prelude.Maybe [OutputDestination])
stopChannelResponse_destinations :: Lens' StopChannelResponse (Maybe [OutputDestination])
stopChannelResponse_destinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe [OutputDestination]
destinations :: Maybe [OutputDestination]
$sel:destinations:StopChannelResponse' :: StopChannelResponse -> Maybe [OutputDestination]
destinations} -> Maybe [OutputDestination]
destinations) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe [OutputDestination]
a -> StopChannelResponse
s {$sel:destinations:StopChannelResponse' :: Maybe [OutputDestination]
destinations = Maybe [OutputDestination]
a} :: StopChannelResponse) 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 endpoints where outgoing connections initiate from
stopChannelResponse_egressEndpoints :: Lens.Lens' StopChannelResponse (Prelude.Maybe [ChannelEgressEndpoint])
stopChannelResponse_egressEndpoints :: Lens' StopChannelResponse (Maybe [ChannelEgressEndpoint])
stopChannelResponse_egressEndpoints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe [ChannelEgressEndpoint]
egressEndpoints :: Maybe [ChannelEgressEndpoint]
$sel:egressEndpoints:StopChannelResponse' :: StopChannelResponse -> Maybe [ChannelEgressEndpoint]
egressEndpoints} -> Maybe [ChannelEgressEndpoint]
egressEndpoints) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe [ChannelEgressEndpoint]
a -> StopChannelResponse
s {$sel:egressEndpoints:StopChannelResponse' :: Maybe [ChannelEgressEndpoint]
egressEndpoints = Maybe [ChannelEgressEndpoint]
a} :: StopChannelResponse) 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

-- | Undocumented member.
stopChannelResponse_encoderSettings :: Lens.Lens' StopChannelResponse (Prelude.Maybe EncoderSettings)
stopChannelResponse_encoderSettings :: Lens' StopChannelResponse (Maybe EncoderSettings)
stopChannelResponse_encoderSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe EncoderSettings
encoderSettings :: Maybe EncoderSettings
$sel:encoderSettings:StopChannelResponse' :: StopChannelResponse -> Maybe EncoderSettings
encoderSettings} -> Maybe EncoderSettings
encoderSettings) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe EncoderSettings
a -> StopChannelResponse
s {$sel:encoderSettings:StopChannelResponse' :: Maybe EncoderSettings
encoderSettings = Maybe EncoderSettings
a} :: StopChannelResponse)

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

-- | List of input attachments for channel.
stopChannelResponse_inputAttachments :: Lens.Lens' StopChannelResponse (Prelude.Maybe [InputAttachment])
stopChannelResponse_inputAttachments :: Lens' StopChannelResponse (Maybe [InputAttachment])
stopChannelResponse_inputAttachments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe [InputAttachment]
inputAttachments :: Maybe [InputAttachment]
$sel:inputAttachments:StopChannelResponse' :: StopChannelResponse -> Maybe [InputAttachment]
inputAttachments} -> Maybe [InputAttachment]
inputAttachments) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe [InputAttachment]
a -> StopChannelResponse
s {$sel:inputAttachments:StopChannelResponse' :: Maybe [InputAttachment]
inputAttachments = Maybe [InputAttachment]
a} :: StopChannelResponse) 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

-- | Specification of network and file inputs for this channel
stopChannelResponse_inputSpecification :: Lens.Lens' StopChannelResponse (Prelude.Maybe InputSpecification)
stopChannelResponse_inputSpecification :: Lens' StopChannelResponse (Maybe InputSpecification)
stopChannelResponse_inputSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe InputSpecification
inputSpecification :: Maybe InputSpecification
$sel:inputSpecification:StopChannelResponse' :: StopChannelResponse -> Maybe InputSpecification
inputSpecification} -> Maybe InputSpecification
inputSpecification) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe InputSpecification
a -> StopChannelResponse
s {$sel:inputSpecification:StopChannelResponse' :: Maybe InputSpecification
inputSpecification = Maybe InputSpecification
a} :: StopChannelResponse)

-- | The log level being written to CloudWatch Logs.
stopChannelResponse_logLevel :: Lens.Lens' StopChannelResponse (Prelude.Maybe LogLevel)
stopChannelResponse_logLevel :: Lens' StopChannelResponse (Maybe LogLevel)
stopChannelResponse_logLevel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe LogLevel
logLevel :: Maybe LogLevel
$sel:logLevel:StopChannelResponse' :: StopChannelResponse -> Maybe LogLevel
logLevel} -> Maybe LogLevel
logLevel) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe LogLevel
a -> StopChannelResponse
s {$sel:logLevel:StopChannelResponse' :: Maybe LogLevel
logLevel = Maybe LogLevel
a} :: StopChannelResponse)

-- | Maintenance settings for this channel.
stopChannelResponse_maintenance :: Lens.Lens' StopChannelResponse (Prelude.Maybe MaintenanceStatus)
stopChannelResponse_maintenance :: Lens' StopChannelResponse (Maybe MaintenanceStatus)
stopChannelResponse_maintenance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe MaintenanceStatus
maintenance :: Maybe MaintenanceStatus
$sel:maintenance:StopChannelResponse' :: StopChannelResponse -> Maybe MaintenanceStatus
maintenance} -> Maybe MaintenanceStatus
maintenance) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe MaintenanceStatus
a -> StopChannelResponse
s {$sel:maintenance:StopChannelResponse' :: Maybe MaintenanceStatus
maintenance = Maybe MaintenanceStatus
a} :: StopChannelResponse)

-- | The name of the channel. (user-mutable)
stopChannelResponse_name :: Lens.Lens' StopChannelResponse (Prelude.Maybe Prelude.Text)
stopChannelResponse_name :: Lens' StopChannelResponse (Maybe Text)
stopChannelResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe Text
name :: Maybe Text
$sel:name:StopChannelResponse' :: StopChannelResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe Text
a -> StopChannelResponse
s {$sel:name:StopChannelResponse' :: Maybe Text
name = Maybe Text
a} :: StopChannelResponse)

-- | Runtime details for the pipelines of a running channel.
stopChannelResponse_pipelineDetails :: Lens.Lens' StopChannelResponse (Prelude.Maybe [PipelineDetail])
stopChannelResponse_pipelineDetails :: Lens' StopChannelResponse (Maybe [PipelineDetail])
stopChannelResponse_pipelineDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe [PipelineDetail]
pipelineDetails :: Maybe [PipelineDetail]
$sel:pipelineDetails:StopChannelResponse' :: StopChannelResponse -> Maybe [PipelineDetail]
pipelineDetails} -> Maybe [PipelineDetail]
pipelineDetails) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe [PipelineDetail]
a -> StopChannelResponse
s {$sel:pipelineDetails:StopChannelResponse' :: Maybe [PipelineDetail]
pipelineDetails = Maybe [PipelineDetail]
a} :: StopChannelResponse) 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 number of currently healthy pipelines.
stopChannelResponse_pipelinesRunningCount :: Lens.Lens' StopChannelResponse (Prelude.Maybe Prelude.Int)
stopChannelResponse_pipelinesRunningCount :: Lens' StopChannelResponse (Maybe Int)
stopChannelResponse_pipelinesRunningCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe Int
pipelinesRunningCount :: Maybe Int
$sel:pipelinesRunningCount:StopChannelResponse' :: StopChannelResponse -> Maybe Int
pipelinesRunningCount} -> Maybe Int
pipelinesRunningCount) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe Int
a -> StopChannelResponse
s {$sel:pipelinesRunningCount:StopChannelResponse' :: Maybe Int
pipelinesRunningCount = Maybe Int
a} :: StopChannelResponse)

-- | The Amazon Resource Name (ARN) of the role assumed when running the
-- Channel.
stopChannelResponse_roleArn :: Lens.Lens' StopChannelResponse (Prelude.Maybe Prelude.Text)
stopChannelResponse_roleArn :: Lens' StopChannelResponse (Maybe Text)
stopChannelResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:StopChannelResponse' :: StopChannelResponse -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe Text
a -> StopChannelResponse
s {$sel:roleArn:StopChannelResponse' :: Maybe Text
roleArn = Maybe Text
a} :: StopChannelResponse)

-- | Undocumented member.
stopChannelResponse_state :: Lens.Lens' StopChannelResponse (Prelude.Maybe ChannelState)
stopChannelResponse_state :: Lens' StopChannelResponse (Maybe ChannelState)
stopChannelResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe ChannelState
state :: Maybe ChannelState
$sel:state:StopChannelResponse' :: StopChannelResponse -> Maybe ChannelState
state} -> Maybe ChannelState
state) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe ChannelState
a -> StopChannelResponse
s {$sel:state:StopChannelResponse' :: Maybe ChannelState
state = Maybe ChannelState
a} :: StopChannelResponse)

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

-- | Settings for VPC output
stopChannelResponse_vpc :: Lens.Lens' StopChannelResponse (Prelude.Maybe VpcOutputSettingsDescription)
stopChannelResponse_vpc :: Lens' StopChannelResponse (Maybe VpcOutputSettingsDescription)
stopChannelResponse_vpc = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopChannelResponse' {Maybe VpcOutputSettingsDescription
vpc :: Maybe VpcOutputSettingsDescription
$sel:vpc:StopChannelResponse' :: StopChannelResponse -> Maybe VpcOutputSettingsDescription
vpc} -> Maybe VpcOutputSettingsDescription
vpc) (\s :: StopChannelResponse
s@StopChannelResponse' {} Maybe VpcOutputSettingsDescription
a -> StopChannelResponse
s {$sel:vpc:StopChannelResponse' :: Maybe VpcOutputSettingsDescription
vpc = Maybe VpcOutputSettingsDescription
a} :: StopChannelResponse)

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

instance Prelude.NFData StopChannelResponse where
  rnf :: StopChannelResponse -> ()
rnf StopChannelResponse' {Int
Maybe Int
Maybe [ChannelEgressEndpoint]
Maybe [OutputDestination]
Maybe [PipelineDetail]
Maybe [InputAttachment]
Maybe Text
Maybe (HashMap Text Text)
Maybe CdiInputSpecification
Maybe ChannelClass
Maybe ChannelState
Maybe InputSpecification
Maybe LogLevel
Maybe MaintenanceStatus
Maybe VpcOutputSettingsDescription
Maybe EncoderSettings
httpStatus :: Int
vpc :: Maybe VpcOutputSettingsDescription
tags :: Maybe (HashMap Text Text)
state :: Maybe ChannelState
roleArn :: Maybe Text
pipelinesRunningCount :: Maybe Int
pipelineDetails :: Maybe [PipelineDetail]
name :: Maybe Text
maintenance :: Maybe MaintenanceStatus
logLevel :: Maybe LogLevel
inputSpecification :: Maybe InputSpecification
inputAttachments :: Maybe [InputAttachment]
id :: Maybe Text
encoderSettings :: Maybe EncoderSettings
egressEndpoints :: Maybe [ChannelEgressEndpoint]
destinations :: Maybe [OutputDestination]
channelClass :: Maybe ChannelClass
cdiInputSpecification :: Maybe CdiInputSpecification
arn :: Maybe Text
$sel:httpStatus:StopChannelResponse' :: StopChannelResponse -> Int
$sel:vpc:StopChannelResponse' :: StopChannelResponse -> Maybe VpcOutputSettingsDescription
$sel:tags:StopChannelResponse' :: StopChannelResponse -> Maybe (HashMap Text Text)
$sel:state:StopChannelResponse' :: StopChannelResponse -> Maybe ChannelState
$sel:roleArn:StopChannelResponse' :: StopChannelResponse -> Maybe Text
$sel:pipelinesRunningCount:StopChannelResponse' :: StopChannelResponse -> Maybe Int
$sel:pipelineDetails:StopChannelResponse' :: StopChannelResponse -> Maybe [PipelineDetail]
$sel:name:StopChannelResponse' :: StopChannelResponse -> Maybe Text
$sel:maintenance:StopChannelResponse' :: StopChannelResponse -> Maybe MaintenanceStatus
$sel:logLevel:StopChannelResponse' :: StopChannelResponse -> Maybe LogLevel
$sel:inputSpecification:StopChannelResponse' :: StopChannelResponse -> Maybe InputSpecification
$sel:inputAttachments:StopChannelResponse' :: StopChannelResponse -> Maybe [InputAttachment]
$sel:id:StopChannelResponse' :: StopChannelResponse -> Maybe Text
$sel:encoderSettings:StopChannelResponse' :: StopChannelResponse -> Maybe EncoderSettings
$sel:egressEndpoints:StopChannelResponse' :: StopChannelResponse -> Maybe [ChannelEgressEndpoint]
$sel:destinations:StopChannelResponse' :: StopChannelResponse -> Maybe [OutputDestination]
$sel:channelClass:StopChannelResponse' :: StopChannelResponse -> Maybe ChannelClass
$sel:cdiInputSpecification:StopChannelResponse' :: StopChannelResponse -> Maybe CdiInputSpecification
$sel:arn:StopChannelResponse' :: StopChannelResponse -> 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 CdiInputSpecification
cdiInputSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelClass
channelClass
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [OutputDestination]
destinations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ChannelEgressEndpoint]
egressEndpoints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncoderSettings
encoderSettings
      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 [InputAttachment]
inputAttachments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputSpecification
inputSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogLevel
logLevel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MaintenanceStatus
maintenance
      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 [PipelineDetail]
pipelineDetails
      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 Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelState
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 Maybe VpcOutputSettingsDescription
vpc
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus