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

    -- * Request Lenses
    describeInputDeviceThumbnail_inputDeviceId,
    describeInputDeviceThumbnail_accept,

    -- * Destructuring the Response
    DescribeInputDeviceThumbnailResponse (..),
    newDescribeInputDeviceThumbnailResponse,

    -- * Response Lenses
    describeInputDeviceThumbnailResponse_contentLength,
    describeInputDeviceThumbnailResponse_contentType,
    describeInputDeviceThumbnailResponse_eTag,
    describeInputDeviceThumbnailResponse_lastModified,
    describeInputDeviceThumbnailResponse_httpStatus,
    describeInputDeviceThumbnailResponse_body,
  )
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 DescribeInputDeviceThumbnailRequest
--
-- /See:/ 'newDescribeInputDeviceThumbnail' smart constructor.
data DescribeInputDeviceThumbnail = DescribeInputDeviceThumbnail'
  { -- | The unique ID of this input device. For example, hd-123456789abcdef.
    DescribeInputDeviceThumbnail -> Text
inputDeviceId :: Prelude.Text,
    -- | The HTTP Accept header. Indicates the requested type for the thumbnail.
    DescribeInputDeviceThumbnail -> AcceptHeader
accept :: AcceptHeader
  }
  deriving (DescribeInputDeviceThumbnail
-> DescribeInputDeviceThumbnail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeInputDeviceThumbnail
-> DescribeInputDeviceThumbnail -> Bool
$c/= :: DescribeInputDeviceThumbnail
-> DescribeInputDeviceThumbnail -> Bool
== :: DescribeInputDeviceThumbnail
-> DescribeInputDeviceThumbnail -> Bool
$c== :: DescribeInputDeviceThumbnail
-> DescribeInputDeviceThumbnail -> Bool
Prelude.Eq, ReadPrec [DescribeInputDeviceThumbnail]
ReadPrec DescribeInputDeviceThumbnail
Int -> ReadS DescribeInputDeviceThumbnail
ReadS [DescribeInputDeviceThumbnail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeInputDeviceThumbnail]
$creadListPrec :: ReadPrec [DescribeInputDeviceThumbnail]
readPrec :: ReadPrec DescribeInputDeviceThumbnail
$creadPrec :: ReadPrec DescribeInputDeviceThumbnail
readList :: ReadS [DescribeInputDeviceThumbnail]
$creadList :: ReadS [DescribeInputDeviceThumbnail]
readsPrec :: Int -> ReadS DescribeInputDeviceThumbnail
$creadsPrec :: Int -> ReadS DescribeInputDeviceThumbnail
Prelude.Read, Int -> DescribeInputDeviceThumbnail -> ShowS
[DescribeInputDeviceThumbnail] -> ShowS
DescribeInputDeviceThumbnail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeInputDeviceThumbnail] -> ShowS
$cshowList :: [DescribeInputDeviceThumbnail] -> ShowS
show :: DescribeInputDeviceThumbnail -> String
$cshow :: DescribeInputDeviceThumbnail -> String
showsPrec :: Int -> DescribeInputDeviceThumbnail -> ShowS
$cshowsPrec :: Int -> DescribeInputDeviceThumbnail -> ShowS
Prelude.Show, forall x.
Rep DescribeInputDeviceThumbnail x -> DescribeInputDeviceThumbnail
forall x.
DescribeInputDeviceThumbnail -> Rep DescribeInputDeviceThumbnail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeInputDeviceThumbnail x -> DescribeInputDeviceThumbnail
$cfrom :: forall x.
DescribeInputDeviceThumbnail -> Rep DescribeInputDeviceThumbnail x
Prelude.Generic)

-- |
-- Create a value of 'DescribeInputDeviceThumbnail' 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', 'describeInputDeviceThumbnail_inputDeviceId' - The unique ID of this input device. For example, hd-123456789abcdef.
--
-- 'accept', 'describeInputDeviceThumbnail_accept' - The HTTP Accept header. Indicates the requested type for the thumbnail.
newDescribeInputDeviceThumbnail ::
  -- | 'inputDeviceId'
  Prelude.Text ->
  -- | 'accept'
  AcceptHeader ->
  DescribeInputDeviceThumbnail
newDescribeInputDeviceThumbnail :: Text -> AcceptHeader -> DescribeInputDeviceThumbnail
newDescribeInputDeviceThumbnail
  Text
pInputDeviceId_
  AcceptHeader
pAccept_ =
    DescribeInputDeviceThumbnail'
      { $sel:inputDeviceId:DescribeInputDeviceThumbnail' :: Text
inputDeviceId =
          Text
pInputDeviceId_,
        $sel:accept:DescribeInputDeviceThumbnail' :: AcceptHeader
accept = AcceptHeader
pAccept_
      }

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

-- | The HTTP Accept header. Indicates the requested type for the thumbnail.
describeInputDeviceThumbnail_accept :: Lens.Lens' DescribeInputDeviceThumbnail AcceptHeader
describeInputDeviceThumbnail_accept :: Lens' DescribeInputDeviceThumbnail AcceptHeader
describeInputDeviceThumbnail_accept = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceThumbnail' {AcceptHeader
accept :: AcceptHeader
$sel:accept:DescribeInputDeviceThumbnail' :: DescribeInputDeviceThumbnail -> AcceptHeader
accept} -> AcceptHeader
accept) (\s :: DescribeInputDeviceThumbnail
s@DescribeInputDeviceThumbnail' {} AcceptHeader
a -> DescribeInputDeviceThumbnail
s {$sel:accept:DescribeInputDeviceThumbnail' :: AcceptHeader
accept = AcceptHeader
a} :: DescribeInputDeviceThumbnail)

instance Core.AWSRequest DescribeInputDeviceThumbnail where
  type
    AWSResponse DescribeInputDeviceThumbnail =
      DescribeInputDeviceThumbnailResponse
  request :: (Service -> Service)
-> DescribeInputDeviceThumbnail
-> Request DescribeInputDeviceThumbnail
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 DescribeInputDeviceThumbnail
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeInputDeviceThumbnail)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int
 -> ResponseHeaders
 -> ResponseBody
 -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveBody
      ( \Int
s ResponseHeaders
h ResponseBody
x ->
          Maybe Integer
-> Maybe ContentType
-> Maybe Text
-> Maybe POSIX
-> Int
-> ResponseBody
-> DescribeInputDeviceThumbnailResponse
DescribeInputDeviceThumbnailResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Content-Length")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Content-Type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"ETag")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Last-Modified")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure ResponseBody
x)
      )

instance
  Prelude.Hashable
    DescribeInputDeviceThumbnail
  where
  hashWithSalt :: Int -> DescribeInputDeviceThumbnail -> Int
hashWithSalt Int
_salt DescribeInputDeviceThumbnail' {Text
AcceptHeader
accept :: AcceptHeader
inputDeviceId :: Text
$sel:accept:DescribeInputDeviceThumbnail' :: DescribeInputDeviceThumbnail -> AcceptHeader
$sel:inputDeviceId:DescribeInputDeviceThumbnail' :: DescribeInputDeviceThumbnail -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
inputDeviceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AcceptHeader
accept

instance Prelude.NFData DescribeInputDeviceThumbnail where
  rnf :: DescribeInputDeviceThumbnail -> ()
rnf DescribeInputDeviceThumbnail' {Text
AcceptHeader
accept :: AcceptHeader
inputDeviceId :: Text
$sel:accept:DescribeInputDeviceThumbnail' :: DescribeInputDeviceThumbnail -> AcceptHeader
$sel:inputDeviceId:DescribeInputDeviceThumbnail' :: DescribeInputDeviceThumbnail -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
inputDeviceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AcceptHeader
accept

instance Data.ToHeaders DescribeInputDeviceThumbnail where
  toHeaders :: DescribeInputDeviceThumbnail -> ResponseHeaders
toHeaders DescribeInputDeviceThumbnail' {Text
AcceptHeader
accept :: AcceptHeader
inputDeviceId :: Text
$sel:accept:DescribeInputDeviceThumbnail' :: DescribeInputDeviceThumbnail -> AcceptHeader
$sel:inputDeviceId:DescribeInputDeviceThumbnail' :: DescribeInputDeviceThumbnail -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"accept" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# AcceptHeader
accept,
        HeaderName
"Content-Type"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/x-amz-json-1.1" :: Prelude.ByteString)
      ]

instance Data.ToPath DescribeInputDeviceThumbnail where
  toPath :: DescribeInputDeviceThumbnail -> ByteString
toPath DescribeInputDeviceThumbnail' {Text
AcceptHeader
accept :: AcceptHeader
inputDeviceId :: Text
$sel:accept:DescribeInputDeviceThumbnail' :: DescribeInputDeviceThumbnail -> AcceptHeader
$sel:inputDeviceId:DescribeInputDeviceThumbnail' :: DescribeInputDeviceThumbnail -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/prod/inputDevices/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
inputDeviceId,
        ByteString
"/thumbnailData"
      ]

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

-- | Placeholder documentation for DescribeInputDeviceThumbnailResponse
--
-- /See:/ 'newDescribeInputDeviceThumbnailResponse' smart constructor.
data DescribeInputDeviceThumbnailResponse = DescribeInputDeviceThumbnailResponse'
  { -- | The length of the content.
    DescribeInputDeviceThumbnailResponse -> Maybe Integer
contentLength :: Prelude.Maybe Prelude.Integer,
    -- | Specifies the media type of the thumbnail.
    DescribeInputDeviceThumbnailResponse -> Maybe ContentType
contentType :: Prelude.Maybe ContentType,
    -- | The unique, cacheable version of this thumbnail.
    DescribeInputDeviceThumbnailResponse -> Maybe Text
eTag :: Prelude.Maybe Prelude.Text,
    -- | The date and time the thumbnail was last updated at the device.
    DescribeInputDeviceThumbnailResponse -> Maybe POSIX
lastModified :: Prelude.Maybe Data.POSIX,
    -- | The response's http status code.
    DescribeInputDeviceThumbnailResponse -> Int
httpStatus :: Prelude.Int,
    -- | The binary data for the thumbnail that the Link device has most recently
    -- sent to MediaLive.
    DescribeInputDeviceThumbnailResponse -> ResponseBody
body :: Data.ResponseBody
  }
  deriving (Int -> DescribeInputDeviceThumbnailResponse -> ShowS
[DescribeInputDeviceThumbnailResponse] -> ShowS
DescribeInputDeviceThumbnailResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeInputDeviceThumbnailResponse] -> ShowS
$cshowList :: [DescribeInputDeviceThumbnailResponse] -> ShowS
show :: DescribeInputDeviceThumbnailResponse -> String
$cshow :: DescribeInputDeviceThumbnailResponse -> String
showsPrec :: Int -> DescribeInputDeviceThumbnailResponse -> ShowS
$cshowsPrec :: Int -> DescribeInputDeviceThumbnailResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeInputDeviceThumbnailResponse x
-> DescribeInputDeviceThumbnailResponse
forall x.
DescribeInputDeviceThumbnailResponse
-> Rep DescribeInputDeviceThumbnailResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeInputDeviceThumbnailResponse x
-> DescribeInputDeviceThumbnailResponse
$cfrom :: forall x.
DescribeInputDeviceThumbnailResponse
-> Rep DescribeInputDeviceThumbnailResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeInputDeviceThumbnailResponse' 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:
--
-- 'contentLength', 'describeInputDeviceThumbnailResponse_contentLength' - The length of the content.
--
-- 'contentType', 'describeInputDeviceThumbnailResponse_contentType' - Specifies the media type of the thumbnail.
--
-- 'eTag', 'describeInputDeviceThumbnailResponse_eTag' - The unique, cacheable version of this thumbnail.
--
-- 'lastModified', 'describeInputDeviceThumbnailResponse_lastModified' - The date and time the thumbnail was last updated at the device.
--
-- 'httpStatus', 'describeInputDeviceThumbnailResponse_httpStatus' - The response's http status code.
--
-- 'body', 'describeInputDeviceThumbnailResponse_body' - The binary data for the thumbnail that the Link device has most recently
-- sent to MediaLive.
newDescribeInputDeviceThumbnailResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'body'
  Data.ResponseBody ->
  DescribeInputDeviceThumbnailResponse
newDescribeInputDeviceThumbnailResponse :: Int -> ResponseBody -> DescribeInputDeviceThumbnailResponse
newDescribeInputDeviceThumbnailResponse
  Int
pHttpStatus_
  ResponseBody
pBody_ =
    DescribeInputDeviceThumbnailResponse'
      { $sel:contentLength:DescribeInputDeviceThumbnailResponse' :: Maybe Integer
contentLength =
          forall a. Maybe a
Prelude.Nothing,
        $sel:contentType:DescribeInputDeviceThumbnailResponse' :: Maybe ContentType
contentType = forall a. Maybe a
Prelude.Nothing,
        $sel:eTag:DescribeInputDeviceThumbnailResponse' :: Maybe Text
eTag = forall a. Maybe a
Prelude.Nothing,
        $sel:lastModified:DescribeInputDeviceThumbnailResponse' :: Maybe POSIX
lastModified = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeInputDeviceThumbnailResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:body:DescribeInputDeviceThumbnailResponse' :: ResponseBody
body = ResponseBody
pBody_
      }

-- | The length of the content.
describeInputDeviceThumbnailResponse_contentLength :: Lens.Lens' DescribeInputDeviceThumbnailResponse (Prelude.Maybe Prelude.Integer)
describeInputDeviceThumbnailResponse_contentLength :: Lens' DescribeInputDeviceThumbnailResponse (Maybe Integer)
describeInputDeviceThumbnailResponse_contentLength = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceThumbnailResponse' {Maybe Integer
contentLength :: Maybe Integer
$sel:contentLength:DescribeInputDeviceThumbnailResponse' :: DescribeInputDeviceThumbnailResponse -> Maybe Integer
contentLength} -> Maybe Integer
contentLength) (\s :: DescribeInputDeviceThumbnailResponse
s@DescribeInputDeviceThumbnailResponse' {} Maybe Integer
a -> DescribeInputDeviceThumbnailResponse
s {$sel:contentLength:DescribeInputDeviceThumbnailResponse' :: Maybe Integer
contentLength = Maybe Integer
a} :: DescribeInputDeviceThumbnailResponse)

-- | Specifies the media type of the thumbnail.
describeInputDeviceThumbnailResponse_contentType :: Lens.Lens' DescribeInputDeviceThumbnailResponse (Prelude.Maybe ContentType)
describeInputDeviceThumbnailResponse_contentType :: Lens' DescribeInputDeviceThumbnailResponse (Maybe ContentType)
describeInputDeviceThumbnailResponse_contentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceThumbnailResponse' {Maybe ContentType
contentType :: Maybe ContentType
$sel:contentType:DescribeInputDeviceThumbnailResponse' :: DescribeInputDeviceThumbnailResponse -> Maybe ContentType
contentType} -> Maybe ContentType
contentType) (\s :: DescribeInputDeviceThumbnailResponse
s@DescribeInputDeviceThumbnailResponse' {} Maybe ContentType
a -> DescribeInputDeviceThumbnailResponse
s {$sel:contentType:DescribeInputDeviceThumbnailResponse' :: Maybe ContentType
contentType = Maybe ContentType
a} :: DescribeInputDeviceThumbnailResponse)

-- | The unique, cacheable version of this thumbnail.
describeInputDeviceThumbnailResponse_eTag :: Lens.Lens' DescribeInputDeviceThumbnailResponse (Prelude.Maybe Prelude.Text)
describeInputDeviceThumbnailResponse_eTag :: Lens' DescribeInputDeviceThumbnailResponse (Maybe Text)
describeInputDeviceThumbnailResponse_eTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceThumbnailResponse' {Maybe Text
eTag :: Maybe Text
$sel:eTag:DescribeInputDeviceThumbnailResponse' :: DescribeInputDeviceThumbnailResponse -> Maybe Text
eTag} -> Maybe Text
eTag) (\s :: DescribeInputDeviceThumbnailResponse
s@DescribeInputDeviceThumbnailResponse' {} Maybe Text
a -> DescribeInputDeviceThumbnailResponse
s {$sel:eTag:DescribeInputDeviceThumbnailResponse' :: Maybe Text
eTag = Maybe Text
a} :: DescribeInputDeviceThumbnailResponse)

-- | The date and time the thumbnail was last updated at the device.
describeInputDeviceThumbnailResponse_lastModified :: Lens.Lens' DescribeInputDeviceThumbnailResponse (Prelude.Maybe Prelude.UTCTime)
describeInputDeviceThumbnailResponse_lastModified :: Lens' DescribeInputDeviceThumbnailResponse (Maybe UTCTime)
describeInputDeviceThumbnailResponse_lastModified = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceThumbnailResponse' {Maybe POSIX
lastModified :: Maybe POSIX
$sel:lastModified:DescribeInputDeviceThumbnailResponse' :: DescribeInputDeviceThumbnailResponse -> Maybe POSIX
lastModified} -> Maybe POSIX
lastModified) (\s :: DescribeInputDeviceThumbnailResponse
s@DescribeInputDeviceThumbnailResponse' {} Maybe POSIX
a -> DescribeInputDeviceThumbnailResponse
s {$sel:lastModified:DescribeInputDeviceThumbnailResponse' :: Maybe POSIX
lastModified = Maybe POSIX
a} :: DescribeInputDeviceThumbnailResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

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

-- | The binary data for the thumbnail that the Link device has most recently
-- sent to MediaLive.
describeInputDeviceThumbnailResponse_body :: Lens.Lens' DescribeInputDeviceThumbnailResponse Data.ResponseBody
describeInputDeviceThumbnailResponse_body :: Lens' DescribeInputDeviceThumbnailResponse ResponseBody
describeInputDeviceThumbnailResponse_body = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeInputDeviceThumbnailResponse' {ResponseBody
body :: ResponseBody
$sel:body:DescribeInputDeviceThumbnailResponse' :: DescribeInputDeviceThumbnailResponse -> ResponseBody
body} -> ResponseBody
body) (\s :: DescribeInputDeviceThumbnailResponse
s@DescribeInputDeviceThumbnailResponse' {} ResponseBody
a -> DescribeInputDeviceThumbnailResponse
s {$sel:body:DescribeInputDeviceThumbnailResponse' :: ResponseBody
body = ResponseBody
a} :: DescribeInputDeviceThumbnailResponse)