{-# 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.IoTFleetWise.GetDecoderManifest
-- 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 created decoder manifest.
module Amazonka.IoTFleetWise.GetDecoderManifest
  ( -- * Creating a Request
    GetDecoderManifest (..),
    newGetDecoderManifest,

    -- * Request Lenses
    getDecoderManifest_name,

    -- * Destructuring the Response
    GetDecoderManifestResponse (..),
    newGetDecoderManifestResponse,

    -- * Response Lenses
    getDecoderManifestResponse_description,
    getDecoderManifestResponse_modelManifestArn,
    getDecoderManifestResponse_status,
    getDecoderManifestResponse_httpStatus,
    getDecoderManifestResponse_name,
    getDecoderManifestResponse_arn,
    getDecoderManifestResponse_creationTime,
    getDecoderManifestResponse_lastModificationTime,
  )
where

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

-- | /See:/ 'newGetDecoderManifest' smart constructor.
data GetDecoderManifest = GetDecoderManifest'
  { -- | The name of the decoder manifest to retrieve information about.
    GetDecoderManifest -> Text
name :: Prelude.Text
  }
  deriving (GetDecoderManifest -> GetDecoderManifest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDecoderManifest -> GetDecoderManifest -> Bool
$c/= :: GetDecoderManifest -> GetDecoderManifest -> Bool
== :: GetDecoderManifest -> GetDecoderManifest -> Bool
$c== :: GetDecoderManifest -> GetDecoderManifest -> Bool
Prelude.Eq, ReadPrec [GetDecoderManifest]
ReadPrec GetDecoderManifest
Int -> ReadS GetDecoderManifest
ReadS [GetDecoderManifest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDecoderManifest]
$creadListPrec :: ReadPrec [GetDecoderManifest]
readPrec :: ReadPrec GetDecoderManifest
$creadPrec :: ReadPrec GetDecoderManifest
readList :: ReadS [GetDecoderManifest]
$creadList :: ReadS [GetDecoderManifest]
readsPrec :: Int -> ReadS GetDecoderManifest
$creadsPrec :: Int -> ReadS GetDecoderManifest
Prelude.Read, Int -> GetDecoderManifest -> ShowS
[GetDecoderManifest] -> ShowS
GetDecoderManifest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDecoderManifest] -> ShowS
$cshowList :: [GetDecoderManifest] -> ShowS
show :: GetDecoderManifest -> String
$cshow :: GetDecoderManifest -> String
showsPrec :: Int -> GetDecoderManifest -> ShowS
$cshowsPrec :: Int -> GetDecoderManifest -> ShowS
Prelude.Show, forall x. Rep GetDecoderManifest x -> GetDecoderManifest
forall x. GetDecoderManifest -> Rep GetDecoderManifest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDecoderManifest x -> GetDecoderManifest
$cfrom :: forall x. GetDecoderManifest -> Rep GetDecoderManifest x
Prelude.Generic)

-- |
-- Create a value of 'GetDecoderManifest' 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:
--
-- 'name', 'getDecoderManifest_name' - The name of the decoder manifest to retrieve information about.
newGetDecoderManifest ::
  -- | 'name'
  Prelude.Text ->
  GetDecoderManifest
newGetDecoderManifest :: Text -> GetDecoderManifest
newGetDecoderManifest Text
pName_ =
  GetDecoderManifest' {$sel:name:GetDecoderManifest' :: Text
name = Text
pName_}

-- | The name of the decoder manifest to retrieve information about.
getDecoderManifest_name :: Lens.Lens' GetDecoderManifest Prelude.Text
getDecoderManifest_name :: Lens' GetDecoderManifest Text
getDecoderManifest_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDecoderManifest' {Text
name :: Text
$sel:name:GetDecoderManifest' :: GetDecoderManifest -> Text
name} -> Text
name) (\s :: GetDecoderManifest
s@GetDecoderManifest' {} Text
a -> GetDecoderManifest
s {$sel:name:GetDecoderManifest' :: Text
name = Text
a} :: GetDecoderManifest)

instance Core.AWSRequest GetDecoderManifest where
  type
    AWSResponse GetDecoderManifest =
      GetDecoderManifestResponse
  request :: (Service -> Service)
-> GetDecoderManifest -> Request GetDecoderManifest
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetDecoderManifest
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetDecoderManifest)))
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
-> Maybe ManifestStatus
-> Int
-> Text
-> Text
-> POSIX
-> POSIX
-> GetDecoderManifestResponse
GetDecoderManifestResponse'
            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
"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
"modelManifestArn")
            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
"status")
            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
"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 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
"creationTime")
            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
"lastModificationTime")
      )

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

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

instance Data.ToHeaders GetDecoderManifest where
  toHeaders :: GetDecoderManifest -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"IoTAutobahnControlPlane.GetDecoderManifest" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetDecoderManifest where
  toJSON :: GetDecoderManifest -> Value
toJSON GetDecoderManifest' {Text
name :: Text
$sel:name:GetDecoderManifest' :: GetDecoderManifest -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)]
      )

instance Data.ToPath GetDecoderManifest where
  toPath :: GetDecoderManifest -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetDecoderManifestResponse' smart constructor.
data GetDecoderManifestResponse = GetDecoderManifestResponse'
  { -- | A brief description of the decoder manifest.
    GetDecoderManifestResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The ARN of a vehicle model (model manifest) associated with the decoder
    -- manifest.
    GetDecoderManifestResponse -> Maybe Text
modelManifestArn :: Prelude.Maybe Prelude.Text,
    -- | The state of the decoder manifest. If the status is @ACTIVE@, the
    -- decoder manifest can\'t be edited. If the status is marked @DRAFT@, you
    -- can edit the decoder manifest.
    GetDecoderManifestResponse -> Maybe ManifestStatus
status :: Prelude.Maybe ManifestStatus,
    -- | The response's http status code.
    GetDecoderManifestResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the decoder manifest.
    GetDecoderManifestResponse -> Text
name :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the decoder manifest.
    GetDecoderManifestResponse -> Text
arn :: Prelude.Text,
    -- | The time the decoder manifest was created in seconds since epoch
    -- (January 1, 1970 at midnight UTC time).
    GetDecoderManifestResponse -> POSIX
creationTime :: Data.POSIX,
    -- | The time the decoder manifest was last updated in seconds since epoch
    -- (January 1, 1970 at midnight UTC time).
    GetDecoderManifestResponse -> POSIX
lastModificationTime :: Data.POSIX
  }
  deriving (GetDecoderManifestResponse -> GetDecoderManifestResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDecoderManifestResponse -> GetDecoderManifestResponse -> Bool
$c/= :: GetDecoderManifestResponse -> GetDecoderManifestResponse -> Bool
== :: GetDecoderManifestResponse -> GetDecoderManifestResponse -> Bool
$c== :: GetDecoderManifestResponse -> GetDecoderManifestResponse -> Bool
Prelude.Eq, ReadPrec [GetDecoderManifestResponse]
ReadPrec GetDecoderManifestResponse
Int -> ReadS GetDecoderManifestResponse
ReadS [GetDecoderManifestResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDecoderManifestResponse]
$creadListPrec :: ReadPrec [GetDecoderManifestResponse]
readPrec :: ReadPrec GetDecoderManifestResponse
$creadPrec :: ReadPrec GetDecoderManifestResponse
readList :: ReadS [GetDecoderManifestResponse]
$creadList :: ReadS [GetDecoderManifestResponse]
readsPrec :: Int -> ReadS GetDecoderManifestResponse
$creadsPrec :: Int -> ReadS GetDecoderManifestResponse
Prelude.Read, Int -> GetDecoderManifestResponse -> ShowS
[GetDecoderManifestResponse] -> ShowS
GetDecoderManifestResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDecoderManifestResponse] -> ShowS
$cshowList :: [GetDecoderManifestResponse] -> ShowS
show :: GetDecoderManifestResponse -> String
$cshow :: GetDecoderManifestResponse -> String
showsPrec :: Int -> GetDecoderManifestResponse -> ShowS
$cshowsPrec :: Int -> GetDecoderManifestResponse -> ShowS
Prelude.Show, forall x.
Rep GetDecoderManifestResponse x -> GetDecoderManifestResponse
forall x.
GetDecoderManifestResponse -> Rep GetDecoderManifestResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDecoderManifestResponse x -> GetDecoderManifestResponse
$cfrom :: forall x.
GetDecoderManifestResponse -> Rep GetDecoderManifestResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDecoderManifestResponse' 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:
--
-- 'description', 'getDecoderManifestResponse_description' - A brief description of the decoder manifest.
--
-- 'modelManifestArn', 'getDecoderManifestResponse_modelManifestArn' - The ARN of a vehicle model (model manifest) associated with the decoder
-- manifest.
--
-- 'status', 'getDecoderManifestResponse_status' - The state of the decoder manifest. If the status is @ACTIVE@, the
-- decoder manifest can\'t be edited. If the status is marked @DRAFT@, you
-- can edit the decoder manifest.
--
-- 'httpStatus', 'getDecoderManifestResponse_httpStatus' - The response's http status code.
--
-- 'name', 'getDecoderManifestResponse_name' - The name of the decoder manifest.
--
-- 'arn', 'getDecoderManifestResponse_arn' - The Amazon Resource Name (ARN) of the decoder manifest.
--
-- 'creationTime', 'getDecoderManifestResponse_creationTime' - The time the decoder manifest was created in seconds since epoch
-- (January 1, 1970 at midnight UTC time).
--
-- 'lastModificationTime', 'getDecoderManifestResponse_lastModificationTime' - The time the decoder manifest was last updated in seconds since epoch
-- (January 1, 1970 at midnight UTC time).
newGetDecoderManifestResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'name'
  Prelude.Text ->
  -- | 'arn'
  Prelude.Text ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModificationTime'
  Prelude.UTCTime ->
  GetDecoderManifestResponse
newGetDecoderManifestResponse :: Int
-> Text -> Text -> UTCTime -> UTCTime -> GetDecoderManifestResponse
newGetDecoderManifestResponse
  Int
pHttpStatus_
  Text
pName_
  Text
pArn_
  UTCTime
pCreationTime_
  UTCTime
pLastModificationTime_ =
    GetDecoderManifestResponse'
      { $sel:description:GetDecoderManifestResponse' :: Maybe Text
description =
          forall a. Maybe a
Prelude.Nothing,
        $sel:modelManifestArn:GetDecoderManifestResponse' :: Maybe Text
modelManifestArn = forall a. Maybe a
Prelude.Nothing,
        $sel:status:GetDecoderManifestResponse' :: Maybe ManifestStatus
status = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetDecoderManifestResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:name:GetDecoderManifestResponse' :: Text
name = Text
pName_,
        $sel:arn:GetDecoderManifestResponse' :: Text
arn = Text
pArn_,
        $sel:creationTime:GetDecoderManifestResponse' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModificationTime:GetDecoderManifestResponse' :: POSIX
lastModificationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModificationTime_
      }

-- | A brief description of the decoder manifest.
getDecoderManifestResponse_description :: Lens.Lens' GetDecoderManifestResponse (Prelude.Maybe Prelude.Text)
getDecoderManifestResponse_description :: Lens' GetDecoderManifestResponse (Maybe Text)
getDecoderManifestResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDecoderManifestResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetDecoderManifestResponse
s@GetDecoderManifestResponse' {} Maybe Text
a -> GetDecoderManifestResponse
s {$sel:description:GetDecoderManifestResponse' :: Maybe Text
description = Maybe Text
a} :: GetDecoderManifestResponse)

-- | The ARN of a vehicle model (model manifest) associated with the decoder
-- manifest.
getDecoderManifestResponse_modelManifestArn :: Lens.Lens' GetDecoderManifestResponse (Prelude.Maybe Prelude.Text)
getDecoderManifestResponse_modelManifestArn :: Lens' GetDecoderManifestResponse (Maybe Text)
getDecoderManifestResponse_modelManifestArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDecoderManifestResponse' {Maybe Text
modelManifestArn :: Maybe Text
$sel:modelManifestArn:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Maybe Text
modelManifestArn} -> Maybe Text
modelManifestArn) (\s :: GetDecoderManifestResponse
s@GetDecoderManifestResponse' {} Maybe Text
a -> GetDecoderManifestResponse
s {$sel:modelManifestArn:GetDecoderManifestResponse' :: Maybe Text
modelManifestArn = Maybe Text
a} :: GetDecoderManifestResponse)

-- | The state of the decoder manifest. If the status is @ACTIVE@, the
-- decoder manifest can\'t be edited. If the status is marked @DRAFT@, you
-- can edit the decoder manifest.
getDecoderManifestResponse_status :: Lens.Lens' GetDecoderManifestResponse (Prelude.Maybe ManifestStatus)
getDecoderManifestResponse_status :: Lens' GetDecoderManifestResponse (Maybe ManifestStatus)
getDecoderManifestResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDecoderManifestResponse' {Maybe ManifestStatus
status :: Maybe ManifestStatus
$sel:status:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Maybe ManifestStatus
status} -> Maybe ManifestStatus
status) (\s :: GetDecoderManifestResponse
s@GetDecoderManifestResponse' {} Maybe ManifestStatus
a -> GetDecoderManifestResponse
s {$sel:status:GetDecoderManifestResponse' :: Maybe ManifestStatus
status = Maybe ManifestStatus
a} :: GetDecoderManifestResponse)

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

-- | The name of the decoder manifest.
getDecoderManifestResponse_name :: Lens.Lens' GetDecoderManifestResponse Prelude.Text
getDecoderManifestResponse_name :: Lens' GetDecoderManifestResponse Text
getDecoderManifestResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDecoderManifestResponse' {Text
name :: Text
$sel:name:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Text
name} -> Text
name) (\s :: GetDecoderManifestResponse
s@GetDecoderManifestResponse' {} Text
a -> GetDecoderManifestResponse
s {$sel:name:GetDecoderManifestResponse' :: Text
name = Text
a} :: GetDecoderManifestResponse)

-- | The Amazon Resource Name (ARN) of the decoder manifest.
getDecoderManifestResponse_arn :: Lens.Lens' GetDecoderManifestResponse Prelude.Text
getDecoderManifestResponse_arn :: Lens' GetDecoderManifestResponse Text
getDecoderManifestResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDecoderManifestResponse' {Text
arn :: Text
$sel:arn:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Text
arn} -> Text
arn) (\s :: GetDecoderManifestResponse
s@GetDecoderManifestResponse' {} Text
a -> GetDecoderManifestResponse
s {$sel:arn:GetDecoderManifestResponse' :: Text
arn = Text
a} :: GetDecoderManifestResponse)

-- | The time the decoder manifest was created in seconds since epoch
-- (January 1, 1970 at midnight UTC time).
getDecoderManifestResponse_creationTime :: Lens.Lens' GetDecoderManifestResponse Prelude.UTCTime
getDecoderManifestResponse_creationTime :: Lens' GetDecoderManifestResponse UTCTime
getDecoderManifestResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDecoderManifestResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: GetDecoderManifestResponse
s@GetDecoderManifestResponse' {} POSIX
a -> GetDecoderManifestResponse
s {$sel:creationTime:GetDecoderManifestResponse' :: POSIX
creationTime = POSIX
a} :: GetDecoderManifestResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The time the decoder manifest was last updated in seconds since epoch
-- (January 1, 1970 at midnight UTC time).
getDecoderManifestResponse_lastModificationTime :: Lens.Lens' GetDecoderManifestResponse Prelude.UTCTime
getDecoderManifestResponse_lastModificationTime :: Lens' GetDecoderManifestResponse UTCTime
getDecoderManifestResponse_lastModificationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDecoderManifestResponse' {POSIX
lastModificationTime :: POSIX
$sel:lastModificationTime:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> POSIX
lastModificationTime} -> POSIX
lastModificationTime) (\s :: GetDecoderManifestResponse
s@GetDecoderManifestResponse' {} POSIX
a -> GetDecoderManifestResponse
s {$sel:lastModificationTime:GetDecoderManifestResponse' :: POSIX
lastModificationTime = POSIX
a} :: GetDecoderManifestResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.NFData GetDecoderManifestResponse where
  rnf :: GetDecoderManifestResponse -> ()
rnf GetDecoderManifestResponse' {Int
Maybe Text
Maybe ManifestStatus
Text
POSIX
lastModificationTime :: POSIX
creationTime :: POSIX
arn :: Text
name :: Text
httpStatus :: Int
status :: Maybe ManifestStatus
modelManifestArn :: Maybe Text
description :: Maybe Text
$sel:lastModificationTime:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> POSIX
$sel:creationTime:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> POSIX
$sel:arn:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Text
$sel:name:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Text
$sel:httpStatus:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Int
$sel:status:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Maybe ManifestStatus
$sel:modelManifestArn:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Maybe Text
$sel:description:GetDecoderManifestResponse' :: GetDecoderManifestResponse -> Maybe Text
..} =
    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
modelManifestArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ManifestStatus
status
      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
name
      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
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastModificationTime