{-# 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.IotTwinMaker.GetScene
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about a scene.
module Amazonka.IotTwinMaker.GetScene
  ( -- * Creating a Request
    GetScene (..),
    newGetScene,

    -- * Request Lenses
    getScene_workspaceId,
    getScene_sceneId,

    -- * Destructuring the Response
    GetSceneResponse (..),
    newGetSceneResponse,

    -- * Response Lenses
    getSceneResponse_capabilities,
    getSceneResponse_description,
    getSceneResponse_httpStatus,
    getSceneResponse_workspaceId,
    getSceneResponse_sceneId,
    getSceneResponse_contentLocation,
    getSceneResponse_arn,
    getSceneResponse_creationDateTime,
    getSceneResponse_updateDateTime,
  )
where

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

-- | /See:/ 'newGetScene' smart constructor.
data GetScene = GetScene'
  { -- | The ID of the workspace that contains the scene.
    GetScene -> Text
workspaceId :: Prelude.Text,
    -- | The ID of the scene.
    GetScene -> Text
sceneId :: Prelude.Text
  }
  deriving (GetScene -> GetScene -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetScene -> GetScene -> Bool
$c/= :: GetScene -> GetScene -> Bool
== :: GetScene -> GetScene -> Bool
$c== :: GetScene -> GetScene -> Bool
Prelude.Eq, ReadPrec [GetScene]
ReadPrec GetScene
Int -> ReadS GetScene
ReadS [GetScene]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetScene]
$creadListPrec :: ReadPrec [GetScene]
readPrec :: ReadPrec GetScene
$creadPrec :: ReadPrec GetScene
readList :: ReadS [GetScene]
$creadList :: ReadS [GetScene]
readsPrec :: Int -> ReadS GetScene
$creadsPrec :: Int -> ReadS GetScene
Prelude.Read, Int -> GetScene -> ShowS
[GetScene] -> ShowS
GetScene -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetScene] -> ShowS
$cshowList :: [GetScene] -> ShowS
show :: GetScene -> String
$cshow :: GetScene -> String
showsPrec :: Int -> GetScene -> ShowS
$cshowsPrec :: Int -> GetScene -> ShowS
Prelude.Show, forall x. Rep GetScene x -> GetScene
forall x. GetScene -> Rep GetScene x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetScene x -> GetScene
$cfrom :: forall x. GetScene -> Rep GetScene x
Prelude.Generic)

-- |
-- Create a value of 'GetScene' 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:
--
-- 'workspaceId', 'getScene_workspaceId' - The ID of the workspace that contains the scene.
--
-- 'sceneId', 'getScene_sceneId' - The ID of the scene.
newGetScene ::
  -- | 'workspaceId'
  Prelude.Text ->
  -- | 'sceneId'
  Prelude.Text ->
  GetScene
newGetScene :: Text -> Text -> GetScene
newGetScene Text
pWorkspaceId_ Text
pSceneId_ =
  GetScene'
    { $sel:workspaceId:GetScene' :: Text
workspaceId = Text
pWorkspaceId_,
      $sel:sceneId:GetScene' :: Text
sceneId = Text
pSceneId_
    }

-- | The ID of the workspace that contains the scene.
getScene_workspaceId :: Lens.Lens' GetScene Prelude.Text
getScene_workspaceId :: Lens' GetScene Text
getScene_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetScene' {Text
workspaceId :: Text
$sel:workspaceId:GetScene' :: GetScene -> Text
workspaceId} -> Text
workspaceId) (\s :: GetScene
s@GetScene' {} Text
a -> GetScene
s {$sel:workspaceId:GetScene' :: Text
workspaceId = Text
a} :: GetScene)

-- | The ID of the scene.
getScene_sceneId :: Lens.Lens' GetScene Prelude.Text
getScene_sceneId :: Lens' GetScene Text
getScene_sceneId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetScene' {Text
sceneId :: Text
$sel:sceneId:GetScene' :: GetScene -> Text
sceneId} -> Text
sceneId) (\s :: GetScene
s@GetScene' {} Text
a -> GetScene
s {$sel:sceneId:GetScene' :: Text
sceneId = Text
a} :: GetScene)

instance Core.AWSRequest GetScene where
  type AWSResponse GetScene = GetSceneResponse
  request :: (Service -> Service) -> GetScene -> Request GetScene
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 GetScene
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetScene)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [Text]
-> Maybe Text
-> Int
-> Text
-> Text
-> Text
-> Text
-> POSIX
-> POSIX
-> GetSceneResponse
GetSceneResponse'
            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
"capabilities" 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
"description")
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"workspaceId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"sceneId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"contentLocation")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String 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 a
Data..:> Key
"creationDateTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"updateDateTime")
      )

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

instance Prelude.NFData GetScene where
  rnf :: GetScene -> ()
rnf GetScene' {Text
sceneId :: Text
workspaceId :: Text
$sel:sceneId:GetScene' :: GetScene -> Text
$sel:workspaceId:GetScene' :: GetScene -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
workspaceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sceneId

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

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

-- | /See:/ 'newGetSceneResponse' smart constructor.
data GetSceneResponse = GetSceneResponse'
  { -- | A list of capabilities that the scene uses to render.
    GetSceneResponse -> Maybe [Text]
capabilities :: Prelude.Maybe [Prelude.Text],
    -- | The description of the scene.
    GetSceneResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetSceneResponse -> Int
httpStatus :: Prelude.Int,
    -- | The ID of the workspace that contains the scene.
    GetSceneResponse -> Text
workspaceId :: Prelude.Text,
    -- | The ID of the scene.
    GetSceneResponse -> Text
sceneId :: Prelude.Text,
    -- | The relative path that specifies the location of the content definition
    -- file.
    GetSceneResponse -> Text
contentLocation :: Prelude.Text,
    -- | The ARN of the scene.
    GetSceneResponse -> Text
arn :: Prelude.Text,
    -- | The date and time when the scene was created.
    GetSceneResponse -> POSIX
creationDateTime :: Data.POSIX,
    -- | The date and time when the scene was last updated.
    GetSceneResponse -> POSIX
updateDateTime :: Data.POSIX
  }
  deriving (GetSceneResponse -> GetSceneResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSceneResponse -> GetSceneResponse -> Bool
$c/= :: GetSceneResponse -> GetSceneResponse -> Bool
== :: GetSceneResponse -> GetSceneResponse -> Bool
$c== :: GetSceneResponse -> GetSceneResponse -> Bool
Prelude.Eq, ReadPrec [GetSceneResponse]
ReadPrec GetSceneResponse
Int -> ReadS GetSceneResponse
ReadS [GetSceneResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSceneResponse]
$creadListPrec :: ReadPrec [GetSceneResponse]
readPrec :: ReadPrec GetSceneResponse
$creadPrec :: ReadPrec GetSceneResponse
readList :: ReadS [GetSceneResponse]
$creadList :: ReadS [GetSceneResponse]
readsPrec :: Int -> ReadS GetSceneResponse
$creadsPrec :: Int -> ReadS GetSceneResponse
Prelude.Read, Int -> GetSceneResponse -> ShowS
[GetSceneResponse] -> ShowS
GetSceneResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSceneResponse] -> ShowS
$cshowList :: [GetSceneResponse] -> ShowS
show :: GetSceneResponse -> String
$cshow :: GetSceneResponse -> String
showsPrec :: Int -> GetSceneResponse -> ShowS
$cshowsPrec :: Int -> GetSceneResponse -> ShowS
Prelude.Show, forall x. Rep GetSceneResponse x -> GetSceneResponse
forall x. GetSceneResponse -> Rep GetSceneResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSceneResponse x -> GetSceneResponse
$cfrom :: forall x. GetSceneResponse -> Rep GetSceneResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSceneResponse' 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:
--
-- 'capabilities', 'getSceneResponse_capabilities' - A list of capabilities that the scene uses to render.
--
-- 'description', 'getSceneResponse_description' - The description of the scene.
--
-- 'httpStatus', 'getSceneResponse_httpStatus' - The response's http status code.
--
-- 'workspaceId', 'getSceneResponse_workspaceId' - The ID of the workspace that contains the scene.
--
-- 'sceneId', 'getSceneResponse_sceneId' - The ID of the scene.
--
-- 'contentLocation', 'getSceneResponse_contentLocation' - The relative path that specifies the location of the content definition
-- file.
--
-- 'arn', 'getSceneResponse_arn' - The ARN of the scene.
--
-- 'creationDateTime', 'getSceneResponse_creationDateTime' - The date and time when the scene was created.
--
-- 'updateDateTime', 'getSceneResponse_updateDateTime' - The date and time when the scene was last updated.
newGetSceneResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'workspaceId'
  Prelude.Text ->
  -- | 'sceneId'
  Prelude.Text ->
  -- | 'contentLocation'
  Prelude.Text ->
  -- | 'arn'
  Prelude.Text ->
  -- | 'creationDateTime'
  Prelude.UTCTime ->
  -- | 'updateDateTime'
  Prelude.UTCTime ->
  GetSceneResponse
newGetSceneResponse :: Int
-> Text
-> Text
-> Text
-> Text
-> UTCTime
-> UTCTime
-> GetSceneResponse
newGetSceneResponse
  Int
pHttpStatus_
  Text
pWorkspaceId_
  Text
pSceneId_
  Text
pContentLocation_
  Text
pArn_
  UTCTime
pCreationDateTime_
  UTCTime
pUpdateDateTime_ =
    GetSceneResponse'
      { $sel:capabilities:GetSceneResponse' :: Maybe [Text]
capabilities = forall a. Maybe a
Prelude.Nothing,
        $sel:description:GetSceneResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetSceneResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:workspaceId:GetSceneResponse' :: Text
workspaceId = Text
pWorkspaceId_,
        $sel:sceneId:GetSceneResponse' :: Text
sceneId = Text
pSceneId_,
        $sel:contentLocation:GetSceneResponse' :: Text
contentLocation = Text
pContentLocation_,
        $sel:arn:GetSceneResponse' :: Text
arn = Text
pArn_,
        $sel:creationDateTime:GetSceneResponse' :: POSIX
creationDateTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationDateTime_,
        $sel:updateDateTime:GetSceneResponse' :: POSIX
updateDateTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pUpdateDateTime_
      }

-- | A list of capabilities that the scene uses to render.
getSceneResponse_capabilities :: Lens.Lens' GetSceneResponse (Prelude.Maybe [Prelude.Text])
getSceneResponse_capabilities :: Lens' GetSceneResponse (Maybe [Text])
getSceneResponse_capabilities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSceneResponse' {Maybe [Text]
capabilities :: Maybe [Text]
$sel:capabilities:GetSceneResponse' :: GetSceneResponse -> Maybe [Text]
capabilities} -> Maybe [Text]
capabilities) (\s :: GetSceneResponse
s@GetSceneResponse' {} Maybe [Text]
a -> GetSceneResponse
s {$sel:capabilities:GetSceneResponse' :: Maybe [Text]
capabilities = Maybe [Text]
a} :: GetSceneResponse) 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 description of the scene.
getSceneResponse_description :: Lens.Lens' GetSceneResponse (Prelude.Maybe Prelude.Text)
getSceneResponse_description :: Lens' GetSceneResponse (Maybe Text)
getSceneResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSceneResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetSceneResponse' :: GetSceneResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetSceneResponse
s@GetSceneResponse' {} Maybe Text
a -> GetSceneResponse
s {$sel:description:GetSceneResponse' :: Maybe Text
description = Maybe Text
a} :: GetSceneResponse)

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

-- | The ID of the workspace that contains the scene.
getSceneResponse_workspaceId :: Lens.Lens' GetSceneResponse Prelude.Text
getSceneResponse_workspaceId :: Lens' GetSceneResponse Text
getSceneResponse_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSceneResponse' {Text
workspaceId :: Text
$sel:workspaceId:GetSceneResponse' :: GetSceneResponse -> Text
workspaceId} -> Text
workspaceId) (\s :: GetSceneResponse
s@GetSceneResponse' {} Text
a -> GetSceneResponse
s {$sel:workspaceId:GetSceneResponse' :: Text
workspaceId = Text
a} :: GetSceneResponse)

-- | The ID of the scene.
getSceneResponse_sceneId :: Lens.Lens' GetSceneResponse Prelude.Text
getSceneResponse_sceneId :: Lens' GetSceneResponse Text
getSceneResponse_sceneId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSceneResponse' {Text
sceneId :: Text
$sel:sceneId:GetSceneResponse' :: GetSceneResponse -> Text
sceneId} -> Text
sceneId) (\s :: GetSceneResponse
s@GetSceneResponse' {} Text
a -> GetSceneResponse
s {$sel:sceneId:GetSceneResponse' :: Text
sceneId = Text
a} :: GetSceneResponse)

-- | The relative path that specifies the location of the content definition
-- file.
getSceneResponse_contentLocation :: Lens.Lens' GetSceneResponse Prelude.Text
getSceneResponse_contentLocation :: Lens' GetSceneResponse Text
getSceneResponse_contentLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSceneResponse' {Text
contentLocation :: Text
$sel:contentLocation:GetSceneResponse' :: GetSceneResponse -> Text
contentLocation} -> Text
contentLocation) (\s :: GetSceneResponse
s@GetSceneResponse' {} Text
a -> GetSceneResponse
s {$sel:contentLocation:GetSceneResponse' :: Text
contentLocation = Text
a} :: GetSceneResponse)

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

-- | The date and time when the scene was created.
getSceneResponse_creationDateTime :: Lens.Lens' GetSceneResponse Prelude.UTCTime
getSceneResponse_creationDateTime :: Lens' GetSceneResponse UTCTime
getSceneResponse_creationDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSceneResponse' {POSIX
creationDateTime :: POSIX
$sel:creationDateTime:GetSceneResponse' :: GetSceneResponse -> POSIX
creationDateTime} -> POSIX
creationDateTime) (\s :: GetSceneResponse
s@GetSceneResponse' {} POSIX
a -> GetSceneResponse
s {$sel:creationDateTime:GetSceneResponse' :: POSIX
creationDateTime = POSIX
a} :: GetSceneResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The date and time when the scene was last updated.
getSceneResponse_updateDateTime :: Lens.Lens' GetSceneResponse Prelude.UTCTime
getSceneResponse_updateDateTime :: Lens' GetSceneResponse UTCTime
getSceneResponse_updateDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSceneResponse' {POSIX
updateDateTime :: POSIX
$sel:updateDateTime:GetSceneResponse' :: GetSceneResponse -> POSIX
updateDateTime} -> POSIX
updateDateTime) (\s :: GetSceneResponse
s@GetSceneResponse' {} POSIX
a -> GetSceneResponse
s {$sel:updateDateTime:GetSceneResponse' :: POSIX
updateDateTime = POSIX
a} :: GetSceneResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.NFData GetSceneResponse where
  rnf :: GetSceneResponse -> ()
rnf GetSceneResponse' {Int
Maybe [Text]
Maybe Text
Text
POSIX
updateDateTime :: POSIX
creationDateTime :: POSIX
arn :: Text
contentLocation :: Text
sceneId :: Text
workspaceId :: Text
httpStatus :: Int
description :: Maybe Text
capabilities :: Maybe [Text]
$sel:updateDateTime:GetSceneResponse' :: GetSceneResponse -> POSIX
$sel:creationDateTime:GetSceneResponse' :: GetSceneResponse -> POSIX
$sel:arn:GetSceneResponse' :: GetSceneResponse -> Text
$sel:contentLocation:GetSceneResponse' :: GetSceneResponse -> Text
$sel:sceneId:GetSceneResponse' :: GetSceneResponse -> Text
$sel:workspaceId:GetSceneResponse' :: GetSceneResponse -> Text
$sel:httpStatus:GetSceneResponse' :: GetSceneResponse -> Int
$sel:description:GetSceneResponse' :: GetSceneResponse -> Maybe Text
$sel:capabilities:GetSceneResponse' :: GetSceneResponse -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
capabilities
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workspaceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sceneId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
contentLocation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
updateDateTime