{-# 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.DescribeInputDevice
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the details for the input device
module Amazonka.MediaLive.DescribeInputDevice
  ( -- * Creating a Request
    DescribeInputDevice (..),
    newDescribeInputDevice,

    -- * Request Lenses
    describeInputDevice_inputDeviceId,

    -- * Destructuring the Response
    DescribeInputDeviceResponse (..),
    newDescribeInputDeviceResponse,

    -- * Response Lenses
    describeInputDeviceResponse_arn,
    describeInputDeviceResponse_connectionState,
    describeInputDeviceResponse_deviceSettingsSyncState,
    describeInputDeviceResponse_deviceUpdateStatus,
    describeInputDeviceResponse_hdDeviceSettings,
    describeInputDeviceResponse_id,
    describeInputDeviceResponse_macAddress,
    describeInputDeviceResponse_name,
    describeInputDeviceResponse_networkSettings,
    describeInputDeviceResponse_serialNumber,
    describeInputDeviceResponse_type,
    describeInputDeviceResponse_uhdDeviceSettings,
    describeInputDeviceResponse_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 DescribeInputDeviceRequest
--
-- /See:/ 'newDescribeInputDevice' smart constructor.
data DescribeInputDevice = DescribeInputDevice'
  { -- | The unique ID of this input device. For example, hd-123456789abcdef.
    DescribeInputDevice -> Text
inputDeviceId :: Prelude.Text
  }
  deriving (DescribeInputDevice -> DescribeInputDevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeInputDevice -> DescribeInputDevice -> Bool
$c/= :: DescribeInputDevice -> DescribeInputDevice -> Bool
== :: DescribeInputDevice -> DescribeInputDevice -> Bool
$c== :: DescribeInputDevice -> DescribeInputDevice -> Bool
Prelude.Eq, ReadPrec [DescribeInputDevice]
ReadPrec DescribeInputDevice
Int -> ReadS DescribeInputDevice
ReadS [DescribeInputDevice]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeInputDevice]
$creadListPrec :: ReadPrec [DescribeInputDevice]
readPrec :: ReadPrec DescribeInputDevice
$creadPrec :: ReadPrec DescribeInputDevice
readList :: ReadS [DescribeInputDevice]
$creadList :: ReadS [DescribeInputDevice]
readsPrec :: Int -> ReadS DescribeInputDevice
$creadsPrec :: Int -> ReadS DescribeInputDevice
Prelude.Read, Int -> DescribeInputDevice -> ShowS
[DescribeInputDevice] -> ShowS
DescribeInputDevice -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeInputDevice] -> ShowS
$cshowList :: [DescribeInputDevice] -> ShowS
show :: DescribeInputDevice -> String
$cshow :: DescribeInputDevice -> String
showsPrec :: Int -> DescribeInputDevice -> ShowS
$cshowsPrec :: Int -> DescribeInputDevice -> ShowS
Prelude.Show, forall x. Rep DescribeInputDevice x -> DescribeInputDevice
forall x. DescribeInputDevice -> Rep DescribeInputDevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeInputDevice x -> DescribeInputDevice
$cfrom :: forall x. DescribeInputDevice -> Rep DescribeInputDevice x
Prelude.Generic)

-- |
-- Create a value of 'DescribeInputDevice' 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:
--
-- 'inputDeviceId', 'describeInputDevice_inputDeviceId' - The unique ID of this input device. For example, hd-123456789abcdef.
newDescribeInputDevice ::
  -- | 'inputDeviceId'
  Prelude.Text ->
  DescribeInputDevice
newDescribeInputDevice :: Text -> DescribeInputDevice
newDescribeInputDevice Text
pInputDeviceId_ =
  DescribeInputDevice'
    { $sel:inputDeviceId:DescribeInputDevice' :: Text
inputDeviceId =
        Text
pInputDeviceId_
    }

-- | The unique ID of this input device. For example, hd-123456789abcdef.
describeInputDevice_inputDeviceId :: Lens.Lens' DescribeInputDevice Prelude.Text
describeInputDevice_inputDeviceId :: Lens' DescribeInputDevice Text
describeInputDevice_inputDeviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDevice' {Text
inputDeviceId :: Text
$sel:inputDeviceId:DescribeInputDevice' :: DescribeInputDevice -> Text
inputDeviceId} -> Text
inputDeviceId) (\s :: DescribeInputDevice
s@DescribeInputDevice' {} Text
a -> DescribeInputDevice
s {$sel:inputDeviceId:DescribeInputDevice' :: Text
inputDeviceId = Text
a} :: DescribeInputDevice)

instance Core.AWSRequest DescribeInputDevice where
  type
    AWSResponse DescribeInputDevice =
      DescribeInputDeviceResponse
  request :: (Service -> Service)
-> DescribeInputDevice -> Request DescribeInputDevice
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeInputDevice
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeInputDevice)))
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 InputDeviceConnectionState
-> Maybe DeviceSettingsSyncState
-> Maybe DeviceUpdateStatus
-> Maybe InputDeviceHdSettings
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe InputDeviceNetworkSettings
-> Maybe Text
-> Maybe InputDeviceType
-> Maybe InputDeviceUhdSettings
-> Int
-> DescribeInputDeviceResponse
DescribeInputDeviceResponse'
            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
"connectionState")
            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
"deviceSettingsSyncState")
            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
"deviceUpdateStatus")
            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
"hdDeviceSettings")
            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
"macAddress")
            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
"networkSettings")
            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
"serialNumber")
            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
"type")
            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
"uhdDeviceSettings")
            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 DescribeInputDevice where
  hashWithSalt :: Int -> DescribeInputDevice -> Int
hashWithSalt Int
_salt DescribeInputDevice' {Text
inputDeviceId :: Text
$sel:inputDeviceId:DescribeInputDevice' :: DescribeInputDevice -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
inputDeviceId

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

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

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

-- | Placeholder documentation for DescribeInputDeviceResponse
--
-- /See:/ 'newDescribeInputDeviceResponse' smart constructor.
data DescribeInputDeviceResponse = DescribeInputDeviceResponse'
  { -- | The unique ARN of the input device.
    DescribeInputDeviceResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The state of the connection between the input device and AWS.
    DescribeInputDeviceResponse -> Maybe InputDeviceConnectionState
connectionState :: Prelude.Maybe InputDeviceConnectionState,
    -- | The status of the action to synchronize the device configuration. If you
    -- change the configuration of the input device (for example, the maximum
    -- bitrate), MediaLive sends the new data to the device. The device might
    -- not update itself immediately. SYNCED means the device has updated its
    -- configuration. SYNCING means that it has not updated its configuration.
    DescribeInputDeviceResponse -> Maybe DeviceSettingsSyncState
deviceSettingsSyncState :: Prelude.Maybe DeviceSettingsSyncState,
    -- | The status of software on the input device.
    DescribeInputDeviceResponse -> Maybe DeviceUpdateStatus
deviceUpdateStatus :: Prelude.Maybe DeviceUpdateStatus,
    -- | Settings that describe an input device that is type HD.
    DescribeInputDeviceResponse -> Maybe InputDeviceHdSettings
hdDeviceSettings :: Prelude.Maybe InputDeviceHdSettings,
    -- | The unique ID of the input device.
    DescribeInputDeviceResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The network MAC address of the input device.
    DescribeInputDeviceResponse -> Maybe Text
macAddress :: Prelude.Maybe Prelude.Text,
    -- | A name that you specify for the input device.
    DescribeInputDeviceResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The network settings for the input device.
    DescribeInputDeviceResponse -> Maybe InputDeviceNetworkSettings
networkSettings :: Prelude.Maybe InputDeviceNetworkSettings,
    -- | The unique serial number of the input device.
    DescribeInputDeviceResponse -> Maybe Text
serialNumber :: Prelude.Maybe Prelude.Text,
    -- | The type of the input device.
    DescribeInputDeviceResponse -> Maybe InputDeviceType
type' :: Prelude.Maybe InputDeviceType,
    -- | Settings that describe an input device that is type UHD.
    DescribeInputDeviceResponse -> Maybe InputDeviceUhdSettings
uhdDeviceSettings :: Prelude.Maybe InputDeviceUhdSettings,
    -- | The response's http status code.
    DescribeInputDeviceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeInputDeviceResponse -> DescribeInputDeviceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeInputDeviceResponse -> DescribeInputDeviceResponse -> Bool
$c/= :: DescribeInputDeviceResponse -> DescribeInputDeviceResponse -> Bool
== :: DescribeInputDeviceResponse -> DescribeInputDeviceResponse -> Bool
$c== :: DescribeInputDeviceResponse -> DescribeInputDeviceResponse -> Bool
Prelude.Eq, ReadPrec [DescribeInputDeviceResponse]
ReadPrec DescribeInputDeviceResponse
Int -> ReadS DescribeInputDeviceResponse
ReadS [DescribeInputDeviceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeInputDeviceResponse]
$creadListPrec :: ReadPrec [DescribeInputDeviceResponse]
readPrec :: ReadPrec DescribeInputDeviceResponse
$creadPrec :: ReadPrec DescribeInputDeviceResponse
readList :: ReadS [DescribeInputDeviceResponse]
$creadList :: ReadS [DescribeInputDeviceResponse]
readsPrec :: Int -> ReadS DescribeInputDeviceResponse
$creadsPrec :: Int -> ReadS DescribeInputDeviceResponse
Prelude.Read, Int -> DescribeInputDeviceResponse -> ShowS
[DescribeInputDeviceResponse] -> ShowS
DescribeInputDeviceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeInputDeviceResponse] -> ShowS
$cshowList :: [DescribeInputDeviceResponse] -> ShowS
show :: DescribeInputDeviceResponse -> String
$cshow :: DescribeInputDeviceResponse -> String
showsPrec :: Int -> DescribeInputDeviceResponse -> ShowS
$cshowsPrec :: Int -> DescribeInputDeviceResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeInputDeviceResponse x -> DescribeInputDeviceResponse
forall x.
DescribeInputDeviceResponse -> Rep DescribeInputDeviceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeInputDeviceResponse x -> DescribeInputDeviceResponse
$cfrom :: forall x.
DescribeInputDeviceResponse -> Rep DescribeInputDeviceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeInputDeviceResponse' 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', 'describeInputDeviceResponse_arn' - The unique ARN of the input device.
--
-- 'connectionState', 'describeInputDeviceResponse_connectionState' - The state of the connection between the input device and AWS.
--
-- 'deviceSettingsSyncState', 'describeInputDeviceResponse_deviceSettingsSyncState' - The status of the action to synchronize the device configuration. If you
-- change the configuration of the input device (for example, the maximum
-- bitrate), MediaLive sends the new data to the device. The device might
-- not update itself immediately. SYNCED means the device has updated its
-- configuration. SYNCING means that it has not updated its configuration.
--
-- 'deviceUpdateStatus', 'describeInputDeviceResponse_deviceUpdateStatus' - The status of software on the input device.
--
-- 'hdDeviceSettings', 'describeInputDeviceResponse_hdDeviceSettings' - Settings that describe an input device that is type HD.
--
-- 'id', 'describeInputDeviceResponse_id' - The unique ID of the input device.
--
-- 'macAddress', 'describeInputDeviceResponse_macAddress' - The network MAC address of the input device.
--
-- 'name', 'describeInputDeviceResponse_name' - A name that you specify for the input device.
--
-- 'networkSettings', 'describeInputDeviceResponse_networkSettings' - The network settings for the input device.
--
-- 'serialNumber', 'describeInputDeviceResponse_serialNumber' - The unique serial number of the input device.
--
-- 'type'', 'describeInputDeviceResponse_type' - The type of the input device.
--
-- 'uhdDeviceSettings', 'describeInputDeviceResponse_uhdDeviceSettings' - Settings that describe an input device that is type UHD.
--
-- 'httpStatus', 'describeInputDeviceResponse_httpStatus' - The response's http status code.
newDescribeInputDeviceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeInputDeviceResponse
newDescribeInputDeviceResponse :: Int -> DescribeInputDeviceResponse
newDescribeInputDeviceResponse Int
pHttpStatus_ =
  DescribeInputDeviceResponse'
    { $sel:arn:DescribeInputDeviceResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:connectionState:DescribeInputDeviceResponse' :: Maybe InputDeviceConnectionState
connectionState = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceSettingsSyncState:DescribeInputDeviceResponse' :: Maybe DeviceSettingsSyncState
deviceSettingsSyncState = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceUpdateStatus:DescribeInputDeviceResponse' :: Maybe DeviceUpdateStatus
deviceUpdateStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:hdDeviceSettings:DescribeInputDeviceResponse' :: Maybe InputDeviceHdSettings
hdDeviceSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:id:DescribeInputDeviceResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:macAddress:DescribeInputDeviceResponse' :: Maybe Text
macAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DescribeInputDeviceResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:networkSettings:DescribeInputDeviceResponse' :: Maybe InputDeviceNetworkSettings
networkSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:serialNumber:DescribeInputDeviceResponse' :: Maybe Text
serialNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:type':DescribeInputDeviceResponse' :: Maybe InputDeviceType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:uhdDeviceSettings:DescribeInputDeviceResponse' :: Maybe InputDeviceUhdSettings
uhdDeviceSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeInputDeviceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The unique ARN of the input device.
describeInputDeviceResponse_arn :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe Prelude.Text)
describeInputDeviceResponse_arn :: Lens' DescribeInputDeviceResponse (Maybe Text)
describeInputDeviceResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe Text
a -> DescribeInputDeviceResponse
s {$sel:arn:DescribeInputDeviceResponse' :: Maybe Text
arn = Maybe Text
a} :: DescribeInputDeviceResponse)

-- | The state of the connection between the input device and AWS.
describeInputDeviceResponse_connectionState :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe InputDeviceConnectionState)
describeInputDeviceResponse_connectionState :: Lens'
  DescribeInputDeviceResponse (Maybe InputDeviceConnectionState)
describeInputDeviceResponse_connectionState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe InputDeviceConnectionState
connectionState :: Maybe InputDeviceConnectionState
$sel:connectionState:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe InputDeviceConnectionState
connectionState} -> Maybe InputDeviceConnectionState
connectionState) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe InputDeviceConnectionState
a -> DescribeInputDeviceResponse
s {$sel:connectionState:DescribeInputDeviceResponse' :: Maybe InputDeviceConnectionState
connectionState = Maybe InputDeviceConnectionState
a} :: DescribeInputDeviceResponse)

-- | The status of the action to synchronize the device configuration. If you
-- change the configuration of the input device (for example, the maximum
-- bitrate), MediaLive sends the new data to the device. The device might
-- not update itself immediately. SYNCED means the device has updated its
-- configuration. SYNCING means that it has not updated its configuration.
describeInputDeviceResponse_deviceSettingsSyncState :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe DeviceSettingsSyncState)
describeInputDeviceResponse_deviceSettingsSyncState :: Lens' DescribeInputDeviceResponse (Maybe DeviceSettingsSyncState)
describeInputDeviceResponse_deviceSettingsSyncState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe DeviceSettingsSyncState
deviceSettingsSyncState :: Maybe DeviceSettingsSyncState
$sel:deviceSettingsSyncState:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe DeviceSettingsSyncState
deviceSettingsSyncState} -> Maybe DeviceSettingsSyncState
deviceSettingsSyncState) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe DeviceSettingsSyncState
a -> DescribeInputDeviceResponse
s {$sel:deviceSettingsSyncState:DescribeInputDeviceResponse' :: Maybe DeviceSettingsSyncState
deviceSettingsSyncState = Maybe DeviceSettingsSyncState
a} :: DescribeInputDeviceResponse)

-- | The status of software on the input device.
describeInputDeviceResponse_deviceUpdateStatus :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe DeviceUpdateStatus)
describeInputDeviceResponse_deviceUpdateStatus :: Lens' DescribeInputDeviceResponse (Maybe DeviceUpdateStatus)
describeInputDeviceResponse_deviceUpdateStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe DeviceUpdateStatus
deviceUpdateStatus :: Maybe DeviceUpdateStatus
$sel:deviceUpdateStatus:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe DeviceUpdateStatus
deviceUpdateStatus} -> Maybe DeviceUpdateStatus
deviceUpdateStatus) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe DeviceUpdateStatus
a -> DescribeInputDeviceResponse
s {$sel:deviceUpdateStatus:DescribeInputDeviceResponse' :: Maybe DeviceUpdateStatus
deviceUpdateStatus = Maybe DeviceUpdateStatus
a} :: DescribeInputDeviceResponse)

-- | Settings that describe an input device that is type HD.
describeInputDeviceResponse_hdDeviceSettings :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe InputDeviceHdSettings)
describeInputDeviceResponse_hdDeviceSettings :: Lens' DescribeInputDeviceResponse (Maybe InputDeviceHdSettings)
describeInputDeviceResponse_hdDeviceSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe InputDeviceHdSettings
hdDeviceSettings :: Maybe InputDeviceHdSettings
$sel:hdDeviceSettings:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe InputDeviceHdSettings
hdDeviceSettings} -> Maybe InputDeviceHdSettings
hdDeviceSettings) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe InputDeviceHdSettings
a -> DescribeInputDeviceResponse
s {$sel:hdDeviceSettings:DescribeInputDeviceResponse' :: Maybe InputDeviceHdSettings
hdDeviceSettings = Maybe InputDeviceHdSettings
a} :: DescribeInputDeviceResponse)

-- | The unique ID of the input device.
describeInputDeviceResponse_id :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe Prelude.Text)
describeInputDeviceResponse_id :: Lens' DescribeInputDeviceResponse (Maybe Text)
describeInputDeviceResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe Text
id :: Maybe Text
$sel:id:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe Text
a -> DescribeInputDeviceResponse
s {$sel:id:DescribeInputDeviceResponse' :: Maybe Text
id = Maybe Text
a} :: DescribeInputDeviceResponse)

-- | The network MAC address of the input device.
describeInputDeviceResponse_macAddress :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe Prelude.Text)
describeInputDeviceResponse_macAddress :: Lens' DescribeInputDeviceResponse (Maybe Text)
describeInputDeviceResponse_macAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe Text
macAddress :: Maybe Text
$sel:macAddress:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe Text
macAddress} -> Maybe Text
macAddress) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe Text
a -> DescribeInputDeviceResponse
s {$sel:macAddress:DescribeInputDeviceResponse' :: Maybe Text
macAddress = Maybe Text
a} :: DescribeInputDeviceResponse)

-- | A name that you specify for the input device.
describeInputDeviceResponse_name :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe Prelude.Text)
describeInputDeviceResponse_name :: Lens' DescribeInputDeviceResponse (Maybe Text)
describeInputDeviceResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe Text
name :: Maybe Text
$sel:name:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe Text
a -> DescribeInputDeviceResponse
s {$sel:name:DescribeInputDeviceResponse' :: Maybe Text
name = Maybe Text
a} :: DescribeInputDeviceResponse)

-- | The network settings for the input device.
describeInputDeviceResponse_networkSettings :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe InputDeviceNetworkSettings)
describeInputDeviceResponse_networkSettings :: Lens'
  DescribeInputDeviceResponse (Maybe InputDeviceNetworkSettings)
describeInputDeviceResponse_networkSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe InputDeviceNetworkSettings
networkSettings :: Maybe InputDeviceNetworkSettings
$sel:networkSettings:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe InputDeviceNetworkSettings
networkSettings} -> Maybe InputDeviceNetworkSettings
networkSettings) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe InputDeviceNetworkSettings
a -> DescribeInputDeviceResponse
s {$sel:networkSettings:DescribeInputDeviceResponse' :: Maybe InputDeviceNetworkSettings
networkSettings = Maybe InputDeviceNetworkSettings
a} :: DescribeInputDeviceResponse)

-- | The unique serial number of the input device.
describeInputDeviceResponse_serialNumber :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe Prelude.Text)
describeInputDeviceResponse_serialNumber :: Lens' DescribeInputDeviceResponse (Maybe Text)
describeInputDeviceResponse_serialNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe Text
serialNumber :: Maybe Text
$sel:serialNumber:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe Text
serialNumber} -> Maybe Text
serialNumber) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe Text
a -> DescribeInputDeviceResponse
s {$sel:serialNumber:DescribeInputDeviceResponse' :: Maybe Text
serialNumber = Maybe Text
a} :: DescribeInputDeviceResponse)

-- | The type of the input device.
describeInputDeviceResponse_type :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe InputDeviceType)
describeInputDeviceResponse_type :: Lens' DescribeInputDeviceResponse (Maybe InputDeviceType)
describeInputDeviceResponse_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe InputDeviceType
type' :: Maybe InputDeviceType
$sel:type':DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe InputDeviceType
type'} -> Maybe InputDeviceType
type') (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe InputDeviceType
a -> DescribeInputDeviceResponse
s {$sel:type':DescribeInputDeviceResponse' :: Maybe InputDeviceType
type' = Maybe InputDeviceType
a} :: DescribeInputDeviceResponse)

-- | Settings that describe an input device that is type UHD.
describeInputDeviceResponse_uhdDeviceSettings :: Lens.Lens' DescribeInputDeviceResponse (Prelude.Maybe InputDeviceUhdSettings)
describeInputDeviceResponse_uhdDeviceSettings :: Lens' DescribeInputDeviceResponse (Maybe InputDeviceUhdSettings)
describeInputDeviceResponse_uhdDeviceSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceResponse' {Maybe InputDeviceUhdSettings
uhdDeviceSettings :: Maybe InputDeviceUhdSettings
$sel:uhdDeviceSettings:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe InputDeviceUhdSettings
uhdDeviceSettings} -> Maybe InputDeviceUhdSettings
uhdDeviceSettings) (\s :: DescribeInputDeviceResponse
s@DescribeInputDeviceResponse' {} Maybe InputDeviceUhdSettings
a -> DescribeInputDeviceResponse
s {$sel:uhdDeviceSettings:DescribeInputDeviceResponse' :: Maybe InputDeviceUhdSettings
uhdDeviceSettings = Maybe InputDeviceUhdSettings
a} :: DescribeInputDeviceResponse)

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

instance Prelude.NFData DescribeInputDeviceResponse where
  rnf :: DescribeInputDeviceResponse -> ()
rnf DescribeInputDeviceResponse' {Int
Maybe Text
Maybe DeviceSettingsSyncState
Maybe DeviceUpdateStatus
Maybe InputDeviceConnectionState
Maybe InputDeviceNetworkSettings
Maybe InputDeviceHdSettings
Maybe InputDeviceType
Maybe InputDeviceUhdSettings
httpStatus :: Int
uhdDeviceSettings :: Maybe InputDeviceUhdSettings
type' :: Maybe InputDeviceType
serialNumber :: Maybe Text
networkSettings :: Maybe InputDeviceNetworkSettings
name :: Maybe Text
macAddress :: Maybe Text
id :: Maybe Text
hdDeviceSettings :: Maybe InputDeviceHdSettings
deviceUpdateStatus :: Maybe DeviceUpdateStatus
deviceSettingsSyncState :: Maybe DeviceSettingsSyncState
connectionState :: Maybe InputDeviceConnectionState
arn :: Maybe Text
$sel:httpStatus:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Int
$sel:uhdDeviceSettings:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe InputDeviceUhdSettings
$sel:type':DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe InputDeviceType
$sel:serialNumber:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe Text
$sel:networkSettings:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe InputDeviceNetworkSettings
$sel:name:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe Text
$sel:macAddress:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe Text
$sel:id:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe Text
$sel:hdDeviceSettings:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe InputDeviceHdSettings
$sel:deviceUpdateStatus:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe DeviceUpdateStatus
$sel:deviceSettingsSyncState:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe DeviceSettingsSyncState
$sel:connectionState:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> Maybe InputDeviceConnectionState
$sel:arn:DescribeInputDeviceResponse' :: DescribeInputDeviceResponse -> 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 InputDeviceConnectionState
connectionState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeviceSettingsSyncState
deviceSettingsSyncState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeviceUpdateStatus
deviceUpdateStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDeviceHdSettings
hdDeviceSettings
      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 Text
macAddress
      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 InputDeviceNetworkSettings
networkSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serialNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDeviceType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputDeviceUhdSettings
uhdDeviceSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus