{-# 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 #-}
module Amazonka.IotTwinMaker.GetEntity
(
GetEntity (..),
newGetEntity,
getEntity_workspaceId,
getEntity_entityId,
GetEntityResponse (..),
newGetEntityResponse,
getEntityResponse_components,
getEntityResponse_description,
getEntityResponse_syncSource,
getEntityResponse_httpStatus,
getEntityResponse_entityId,
getEntityResponse_entityName,
getEntityResponse_arn,
getEntityResponse_status,
getEntityResponse_workspaceId,
getEntityResponse_parentEntityId,
getEntityResponse_hasChildEntities,
getEntityResponse_creationDateTime,
getEntityResponse_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
data GetEntity = GetEntity'
{
GetEntity -> Text
workspaceId :: Prelude.Text,
GetEntity -> Text
entityId :: Prelude.Text
}
deriving (GetEntity -> GetEntity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEntity -> GetEntity -> Bool
$c/= :: GetEntity -> GetEntity -> Bool
== :: GetEntity -> GetEntity -> Bool
$c== :: GetEntity -> GetEntity -> Bool
Prelude.Eq, ReadPrec [GetEntity]
ReadPrec GetEntity
Int -> ReadS GetEntity
ReadS [GetEntity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEntity]
$creadListPrec :: ReadPrec [GetEntity]
readPrec :: ReadPrec GetEntity
$creadPrec :: ReadPrec GetEntity
readList :: ReadS [GetEntity]
$creadList :: ReadS [GetEntity]
readsPrec :: Int -> ReadS GetEntity
$creadsPrec :: Int -> ReadS GetEntity
Prelude.Read, Int -> GetEntity -> ShowS
[GetEntity] -> ShowS
GetEntity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEntity] -> ShowS
$cshowList :: [GetEntity] -> ShowS
show :: GetEntity -> String
$cshow :: GetEntity -> String
showsPrec :: Int -> GetEntity -> ShowS
$cshowsPrec :: Int -> GetEntity -> ShowS
Prelude.Show, forall x. Rep GetEntity x -> GetEntity
forall x. GetEntity -> Rep GetEntity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEntity x -> GetEntity
$cfrom :: forall x. GetEntity -> Rep GetEntity x
Prelude.Generic)
newGetEntity ::
Prelude.Text ->
Prelude.Text ->
GetEntity
newGetEntity :: Text -> Text -> GetEntity
newGetEntity Text
pWorkspaceId_ Text
pEntityId_ =
GetEntity'
{ $sel:workspaceId:GetEntity' :: Text
workspaceId = Text
pWorkspaceId_,
$sel:entityId:GetEntity' :: Text
entityId = Text
pEntityId_
}
getEntity_workspaceId :: Lens.Lens' GetEntity Prelude.Text
getEntity_workspaceId :: Lens' GetEntity Text
getEntity_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntity' {Text
workspaceId :: Text
$sel:workspaceId:GetEntity' :: GetEntity -> Text
workspaceId} -> Text
workspaceId) (\s :: GetEntity
s@GetEntity' {} Text
a -> GetEntity
s {$sel:workspaceId:GetEntity' :: Text
workspaceId = Text
a} :: GetEntity)
getEntity_entityId :: Lens.Lens' GetEntity Prelude.Text
getEntity_entityId :: Lens' GetEntity Text
getEntity_entityId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntity' {Text
entityId :: Text
$sel:entityId:GetEntity' :: GetEntity -> Text
entityId} -> Text
entityId) (\s :: GetEntity
s@GetEntity' {} Text
a -> GetEntity
s {$sel:entityId:GetEntity' :: Text
entityId = Text
a} :: GetEntity)
instance Core.AWSRequest GetEntity where
type AWSResponse GetEntity = GetEntityResponse
request :: (Service -> Service) -> GetEntity -> Request GetEntity
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 GetEntity
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetEntity)))
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 (HashMap Text ComponentResponse)
-> Maybe Text
-> Maybe Text
-> Int
-> Text
-> Text
-> Text
-> Status
-> Text
-> Text
-> Bool
-> POSIX
-> POSIX
-> GetEntityResponse
GetEntityResponse'
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
"components" 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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"syncSource")
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
"entityId")
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
"entityName")
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
"status")
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
"parentEntityId")
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
"hasChildEntities")
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 GetEntity where
hashWithSalt :: Int -> GetEntity -> Int
hashWithSalt Int
_salt GetEntity' {Text
entityId :: Text
workspaceId :: Text
$sel:entityId:GetEntity' :: GetEntity -> Text
$sel:workspaceId:GetEntity' :: GetEntity -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workspaceId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
entityId
instance Prelude.NFData GetEntity where
rnf :: GetEntity -> ()
rnf GetEntity' {Text
entityId :: Text
workspaceId :: Text
$sel:entityId:GetEntity' :: GetEntity -> Text
$sel:workspaceId:GetEntity' :: GetEntity -> 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
entityId
instance Data.ToHeaders GetEntity where
toHeaders :: GetEntity -> 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 GetEntity where
toPath :: GetEntity -> ByteString
toPath GetEntity' {Text
entityId :: Text
workspaceId :: Text
$sel:entityId:GetEntity' :: GetEntity -> Text
$sel:workspaceId:GetEntity' :: GetEntity -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/workspaces/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
workspaceId,
ByteString
"/entities/",
forall a. ToByteString a => a -> ByteString
Data.toBS Text
entityId
]
instance Data.ToQuery GetEntity where
toQuery :: GetEntity -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetEntityResponse = GetEntityResponse'
{
GetEntityResponse -> Maybe (HashMap Text ComponentResponse)
components :: Prelude.Maybe (Prelude.HashMap Prelude.Text ComponentResponse),
GetEntityResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
GetEntityResponse -> Maybe Text
syncSource :: Prelude.Maybe Prelude.Text,
GetEntityResponse -> Int
httpStatus :: Prelude.Int,
GetEntityResponse -> Text
entityId :: Prelude.Text,
GetEntityResponse -> Text
entityName :: Prelude.Text,
GetEntityResponse -> Text
arn :: Prelude.Text,
GetEntityResponse -> Status
status :: Status,
GetEntityResponse -> Text
workspaceId :: Prelude.Text,
GetEntityResponse -> Text
parentEntityId :: Prelude.Text,
GetEntityResponse -> Bool
hasChildEntities :: Prelude.Bool,
GetEntityResponse -> POSIX
creationDateTime :: Data.POSIX,
GetEntityResponse -> POSIX
updateDateTime :: Data.POSIX
}
deriving (GetEntityResponse -> GetEntityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEntityResponse -> GetEntityResponse -> Bool
$c/= :: GetEntityResponse -> GetEntityResponse -> Bool
== :: GetEntityResponse -> GetEntityResponse -> Bool
$c== :: GetEntityResponse -> GetEntityResponse -> Bool
Prelude.Eq, ReadPrec [GetEntityResponse]
ReadPrec GetEntityResponse
Int -> ReadS GetEntityResponse
ReadS [GetEntityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetEntityResponse]
$creadListPrec :: ReadPrec [GetEntityResponse]
readPrec :: ReadPrec GetEntityResponse
$creadPrec :: ReadPrec GetEntityResponse
readList :: ReadS [GetEntityResponse]
$creadList :: ReadS [GetEntityResponse]
readsPrec :: Int -> ReadS GetEntityResponse
$creadsPrec :: Int -> ReadS GetEntityResponse
Prelude.Read, Int -> GetEntityResponse -> ShowS
[GetEntityResponse] -> ShowS
GetEntityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEntityResponse] -> ShowS
$cshowList :: [GetEntityResponse] -> ShowS
show :: GetEntityResponse -> String
$cshow :: GetEntityResponse -> String
showsPrec :: Int -> GetEntityResponse -> ShowS
$cshowsPrec :: Int -> GetEntityResponse -> ShowS
Prelude.Show, forall x. Rep GetEntityResponse x -> GetEntityResponse
forall x. GetEntityResponse -> Rep GetEntityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEntityResponse x -> GetEntityResponse
$cfrom :: forall x. GetEntityResponse -> Rep GetEntityResponse x
Prelude.Generic)
newGetEntityResponse ::
Prelude.Int ->
Prelude.Text ->
Prelude.Text ->
Prelude.Text ->
Status ->
Prelude.Text ->
Prelude.Text ->
Prelude.Bool ->
Prelude.UTCTime ->
Prelude.UTCTime ->
GetEntityResponse
newGetEntityResponse :: Int
-> Text
-> Text
-> Text
-> Status
-> Text
-> Text
-> Bool
-> UTCTime
-> UTCTime
-> GetEntityResponse
newGetEntityResponse
Int
pHttpStatus_
Text
pEntityId_
Text
pEntityName_
Text
pArn_
Status
pStatus_
Text
pWorkspaceId_
Text
pParentEntityId_
Bool
pHasChildEntities_
UTCTime
pCreationDateTime_
UTCTime
pUpdateDateTime_ =
GetEntityResponse'
{ $sel:components:GetEntityResponse' :: Maybe (HashMap Text ComponentResponse)
components = forall a. Maybe a
Prelude.Nothing,
$sel:description:GetEntityResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
$sel:syncSource:GetEntityResponse' :: Maybe Text
syncSource = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:GetEntityResponse' :: Int
httpStatus = Int
pHttpStatus_,
$sel:entityId:GetEntityResponse' :: Text
entityId = Text
pEntityId_,
$sel:entityName:GetEntityResponse' :: Text
entityName = Text
pEntityName_,
$sel:arn:GetEntityResponse' :: Text
arn = Text
pArn_,
$sel:status:GetEntityResponse' :: Status
status = Status
pStatus_,
$sel:workspaceId:GetEntityResponse' :: Text
workspaceId = Text
pWorkspaceId_,
$sel:parentEntityId:GetEntityResponse' :: Text
parentEntityId = Text
pParentEntityId_,
$sel:hasChildEntities:GetEntityResponse' :: Bool
hasChildEntities = Bool
pHasChildEntities_,
$sel:creationDateTime:GetEntityResponse' :: POSIX
creationDateTime =
forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationDateTime_,
$sel:updateDateTime:GetEntityResponse' :: POSIX
updateDateTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pUpdateDateTime_
}
getEntityResponse_components :: Lens.Lens' GetEntityResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text ComponentResponse))
getEntityResponse_components :: Lens' GetEntityResponse (Maybe (HashMap Text ComponentResponse))
getEntityResponse_components = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Maybe (HashMap Text ComponentResponse)
components :: Maybe (HashMap Text ComponentResponse)
$sel:components:GetEntityResponse' :: GetEntityResponse -> Maybe (HashMap Text ComponentResponse)
components} -> Maybe (HashMap Text ComponentResponse)
components) (\s :: GetEntityResponse
s@GetEntityResponse' {} Maybe (HashMap Text ComponentResponse)
a -> GetEntityResponse
s {$sel:components:GetEntityResponse' :: Maybe (HashMap Text ComponentResponse)
components = Maybe (HashMap Text ComponentResponse)
a} :: GetEntityResponse) 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
getEntityResponse_description :: Lens.Lens' GetEntityResponse (Prelude.Maybe Prelude.Text)
getEntityResponse_description :: Lens' GetEntityResponse (Maybe Text)
getEntityResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetEntityResponse' :: GetEntityResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetEntityResponse
s@GetEntityResponse' {} Maybe Text
a -> GetEntityResponse
s {$sel:description:GetEntityResponse' :: Maybe Text
description = Maybe Text
a} :: GetEntityResponse)
getEntityResponse_syncSource :: Lens.Lens' GetEntityResponse (Prelude.Maybe Prelude.Text)
getEntityResponse_syncSource :: Lens' GetEntityResponse (Maybe Text)
getEntityResponse_syncSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Maybe Text
syncSource :: Maybe Text
$sel:syncSource:GetEntityResponse' :: GetEntityResponse -> Maybe Text
syncSource} -> Maybe Text
syncSource) (\s :: GetEntityResponse
s@GetEntityResponse' {} Maybe Text
a -> GetEntityResponse
s {$sel:syncSource:GetEntityResponse' :: Maybe Text
syncSource = Maybe Text
a} :: GetEntityResponse)
getEntityResponse_httpStatus :: Lens.Lens' GetEntityResponse Prelude.Int
getEntityResponse_httpStatus :: Lens' GetEntityResponse Int
getEntityResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetEntityResponse' :: GetEntityResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetEntityResponse
s@GetEntityResponse' {} Int
a -> GetEntityResponse
s {$sel:httpStatus:GetEntityResponse' :: Int
httpStatus = Int
a} :: GetEntityResponse)
getEntityResponse_entityId :: Lens.Lens' GetEntityResponse Prelude.Text
getEntityResponse_entityId :: Lens' GetEntityResponse Text
getEntityResponse_entityId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Text
entityId :: Text
$sel:entityId:GetEntityResponse' :: GetEntityResponse -> Text
entityId} -> Text
entityId) (\s :: GetEntityResponse
s@GetEntityResponse' {} Text
a -> GetEntityResponse
s {$sel:entityId:GetEntityResponse' :: Text
entityId = Text
a} :: GetEntityResponse)
getEntityResponse_entityName :: Lens.Lens' GetEntityResponse Prelude.Text
getEntityResponse_entityName :: Lens' GetEntityResponse Text
getEntityResponse_entityName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Text
entityName :: Text
$sel:entityName:GetEntityResponse' :: GetEntityResponse -> Text
entityName} -> Text
entityName) (\s :: GetEntityResponse
s@GetEntityResponse' {} Text
a -> GetEntityResponse
s {$sel:entityName:GetEntityResponse' :: Text
entityName = Text
a} :: GetEntityResponse)
getEntityResponse_arn :: Lens.Lens' GetEntityResponse Prelude.Text
getEntityResponse_arn :: Lens' GetEntityResponse Text
getEntityResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Text
arn :: Text
$sel:arn:GetEntityResponse' :: GetEntityResponse -> Text
arn} -> Text
arn) (\s :: GetEntityResponse
s@GetEntityResponse' {} Text
a -> GetEntityResponse
s {$sel:arn:GetEntityResponse' :: Text
arn = Text
a} :: GetEntityResponse)
getEntityResponse_status :: Lens.Lens' GetEntityResponse Status
getEntityResponse_status :: Lens' GetEntityResponse Status
getEntityResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Status
status :: Status
$sel:status:GetEntityResponse' :: GetEntityResponse -> Status
status} -> Status
status) (\s :: GetEntityResponse
s@GetEntityResponse' {} Status
a -> GetEntityResponse
s {$sel:status:GetEntityResponse' :: Status
status = Status
a} :: GetEntityResponse)
getEntityResponse_workspaceId :: Lens.Lens' GetEntityResponse Prelude.Text
getEntityResponse_workspaceId :: Lens' GetEntityResponse Text
getEntityResponse_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Text
workspaceId :: Text
$sel:workspaceId:GetEntityResponse' :: GetEntityResponse -> Text
workspaceId} -> Text
workspaceId) (\s :: GetEntityResponse
s@GetEntityResponse' {} Text
a -> GetEntityResponse
s {$sel:workspaceId:GetEntityResponse' :: Text
workspaceId = Text
a} :: GetEntityResponse)
getEntityResponse_parentEntityId :: Lens.Lens' GetEntityResponse Prelude.Text
getEntityResponse_parentEntityId :: Lens' GetEntityResponse Text
getEntityResponse_parentEntityId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Text
parentEntityId :: Text
$sel:parentEntityId:GetEntityResponse' :: GetEntityResponse -> Text
parentEntityId} -> Text
parentEntityId) (\s :: GetEntityResponse
s@GetEntityResponse' {} Text
a -> GetEntityResponse
s {$sel:parentEntityId:GetEntityResponse' :: Text
parentEntityId = Text
a} :: GetEntityResponse)
getEntityResponse_hasChildEntities :: Lens.Lens' GetEntityResponse Prelude.Bool
getEntityResponse_hasChildEntities :: Lens' GetEntityResponse Bool
getEntityResponse_hasChildEntities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {Bool
hasChildEntities :: Bool
$sel:hasChildEntities:GetEntityResponse' :: GetEntityResponse -> Bool
hasChildEntities} -> Bool
hasChildEntities) (\s :: GetEntityResponse
s@GetEntityResponse' {} Bool
a -> GetEntityResponse
s {$sel:hasChildEntities:GetEntityResponse' :: Bool
hasChildEntities = Bool
a} :: GetEntityResponse)
getEntityResponse_creationDateTime :: Lens.Lens' GetEntityResponse Prelude.UTCTime
getEntityResponse_creationDateTime :: Lens' GetEntityResponse UTCTime
getEntityResponse_creationDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {POSIX
creationDateTime :: POSIX
$sel:creationDateTime:GetEntityResponse' :: GetEntityResponse -> POSIX
creationDateTime} -> POSIX
creationDateTime) (\s :: GetEntityResponse
s@GetEntityResponse' {} POSIX
a -> GetEntityResponse
s {$sel:creationDateTime:GetEntityResponse' :: POSIX
creationDateTime = POSIX
a} :: GetEntityResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
getEntityResponse_updateDateTime :: Lens.Lens' GetEntityResponse Prelude.UTCTime
getEntityResponse_updateDateTime :: Lens' GetEntityResponse UTCTime
getEntityResponse_updateDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetEntityResponse' {POSIX
updateDateTime :: POSIX
$sel:updateDateTime:GetEntityResponse' :: GetEntityResponse -> POSIX
updateDateTime} -> POSIX
updateDateTime) (\s :: GetEntityResponse
s@GetEntityResponse' {} POSIX
a -> GetEntityResponse
s {$sel:updateDateTime:GetEntityResponse' :: POSIX
updateDateTime = POSIX
a} :: GetEntityResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
instance Prelude.NFData GetEntityResponse where
rnf :: GetEntityResponse -> ()
rnf GetEntityResponse' {Bool
Int
Maybe Text
Maybe (HashMap Text ComponentResponse)
Text
POSIX
Status
updateDateTime :: POSIX
creationDateTime :: POSIX
hasChildEntities :: Bool
parentEntityId :: Text
workspaceId :: Text
status :: Status
arn :: Text
entityName :: Text
entityId :: Text
httpStatus :: Int
syncSource :: Maybe Text
description :: Maybe Text
components :: Maybe (HashMap Text ComponentResponse)
$sel:updateDateTime:GetEntityResponse' :: GetEntityResponse -> POSIX
$sel:creationDateTime:GetEntityResponse' :: GetEntityResponse -> POSIX
$sel:hasChildEntities:GetEntityResponse' :: GetEntityResponse -> Bool
$sel:parentEntityId:GetEntityResponse' :: GetEntityResponse -> Text
$sel:workspaceId:GetEntityResponse' :: GetEntityResponse -> Text
$sel:status:GetEntityResponse' :: GetEntityResponse -> Status
$sel:arn:GetEntityResponse' :: GetEntityResponse -> Text
$sel:entityName:GetEntityResponse' :: GetEntityResponse -> Text
$sel:entityId:GetEntityResponse' :: GetEntityResponse -> Text
$sel:httpStatus:GetEntityResponse' :: GetEntityResponse -> Int
$sel:syncSource:GetEntityResponse' :: GetEntityResponse -> Maybe Text
$sel:description:GetEntityResponse' :: GetEntityResponse -> Maybe Text
$sel:components:GetEntityResponse' :: GetEntityResponse -> Maybe (HashMap Text ComponentResponse)
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text ComponentResponse)
components
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 Maybe Text
syncSource
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
entityId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
entityName
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 Status
status
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
parentEntityId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
hasChildEntities
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