{-# 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.Greengrass.CreateDeviceDefinition
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a device definition. You may provide the initial version of the
-- device definition now or use \'\'CreateDeviceDefinitionVersion\'\' at a
-- later time.
module Amazonka.Greengrass.CreateDeviceDefinition
  ( -- * Creating a Request
    CreateDeviceDefinition (..),
    newCreateDeviceDefinition,

    -- * Request Lenses
    createDeviceDefinition_amznClientToken,
    createDeviceDefinition_initialVersion,
    createDeviceDefinition_name,
    createDeviceDefinition_tags,

    -- * Destructuring the Response
    CreateDeviceDefinitionResponse (..),
    newCreateDeviceDefinitionResponse,

    -- * Response Lenses
    createDeviceDefinitionResponse_arn,
    createDeviceDefinitionResponse_creationTimestamp,
    createDeviceDefinitionResponse_id,
    createDeviceDefinitionResponse_lastUpdatedTimestamp,
    createDeviceDefinitionResponse_latestVersion,
    createDeviceDefinitionResponse_latestVersionArn,
    createDeviceDefinitionResponse_name,
    createDeviceDefinitionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateDeviceDefinition' smart constructor.
data CreateDeviceDefinition = CreateDeviceDefinition'
  { -- | A client token used to correlate requests and responses.
    CreateDeviceDefinition -> Maybe Text
amznClientToken :: Prelude.Maybe Prelude.Text,
    -- | Information about the initial version of the device definition.
    CreateDeviceDefinition -> Maybe DeviceDefinitionVersion
initialVersion :: Prelude.Maybe DeviceDefinitionVersion,
    -- | The name of the device definition.
    CreateDeviceDefinition -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Tag(s) to add to the new resource.
    CreateDeviceDefinition -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text)
  }
  deriving (CreateDeviceDefinition -> CreateDeviceDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDeviceDefinition -> CreateDeviceDefinition -> Bool
$c/= :: CreateDeviceDefinition -> CreateDeviceDefinition -> Bool
== :: CreateDeviceDefinition -> CreateDeviceDefinition -> Bool
$c== :: CreateDeviceDefinition -> CreateDeviceDefinition -> Bool
Prelude.Eq, ReadPrec [CreateDeviceDefinition]
ReadPrec CreateDeviceDefinition
Int -> ReadS CreateDeviceDefinition
ReadS [CreateDeviceDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDeviceDefinition]
$creadListPrec :: ReadPrec [CreateDeviceDefinition]
readPrec :: ReadPrec CreateDeviceDefinition
$creadPrec :: ReadPrec CreateDeviceDefinition
readList :: ReadS [CreateDeviceDefinition]
$creadList :: ReadS [CreateDeviceDefinition]
readsPrec :: Int -> ReadS CreateDeviceDefinition
$creadsPrec :: Int -> ReadS CreateDeviceDefinition
Prelude.Read, Int -> CreateDeviceDefinition -> ShowS
[CreateDeviceDefinition] -> ShowS
CreateDeviceDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDeviceDefinition] -> ShowS
$cshowList :: [CreateDeviceDefinition] -> ShowS
show :: CreateDeviceDefinition -> String
$cshow :: CreateDeviceDefinition -> String
showsPrec :: Int -> CreateDeviceDefinition -> ShowS
$cshowsPrec :: Int -> CreateDeviceDefinition -> ShowS
Prelude.Show, forall x. Rep CreateDeviceDefinition x -> CreateDeviceDefinition
forall x. CreateDeviceDefinition -> Rep CreateDeviceDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateDeviceDefinition x -> CreateDeviceDefinition
$cfrom :: forall x. CreateDeviceDefinition -> Rep CreateDeviceDefinition x
Prelude.Generic)

-- |
-- Create a value of 'CreateDeviceDefinition' 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:
--
-- 'amznClientToken', 'createDeviceDefinition_amznClientToken' - A client token used to correlate requests and responses.
--
-- 'initialVersion', 'createDeviceDefinition_initialVersion' - Information about the initial version of the device definition.
--
-- 'name', 'createDeviceDefinition_name' - The name of the device definition.
--
-- 'tags', 'createDeviceDefinition_tags' - Tag(s) to add to the new resource.
newCreateDeviceDefinition ::
  CreateDeviceDefinition
newCreateDeviceDefinition :: CreateDeviceDefinition
newCreateDeviceDefinition =
  CreateDeviceDefinition'
    { $sel:amznClientToken:CreateDeviceDefinition' :: Maybe Text
amznClientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:initialVersion:CreateDeviceDefinition' :: Maybe DeviceDefinitionVersion
initialVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateDeviceDefinition' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateDeviceDefinition' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing
    }

-- | A client token used to correlate requests and responses.
createDeviceDefinition_amznClientToken :: Lens.Lens' CreateDeviceDefinition (Prelude.Maybe Prelude.Text)
createDeviceDefinition_amznClientToken :: Lens' CreateDeviceDefinition (Maybe Text)
createDeviceDefinition_amznClientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceDefinition' {Maybe Text
amznClientToken :: Maybe Text
$sel:amznClientToken:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe Text
amznClientToken} -> Maybe Text
amznClientToken) (\s :: CreateDeviceDefinition
s@CreateDeviceDefinition' {} Maybe Text
a -> CreateDeviceDefinition
s {$sel:amznClientToken:CreateDeviceDefinition' :: Maybe Text
amznClientToken = Maybe Text
a} :: CreateDeviceDefinition)

-- | Information about the initial version of the device definition.
createDeviceDefinition_initialVersion :: Lens.Lens' CreateDeviceDefinition (Prelude.Maybe DeviceDefinitionVersion)
createDeviceDefinition_initialVersion :: Lens' CreateDeviceDefinition (Maybe DeviceDefinitionVersion)
createDeviceDefinition_initialVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceDefinition' {Maybe DeviceDefinitionVersion
initialVersion :: Maybe DeviceDefinitionVersion
$sel:initialVersion:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe DeviceDefinitionVersion
initialVersion} -> Maybe DeviceDefinitionVersion
initialVersion) (\s :: CreateDeviceDefinition
s@CreateDeviceDefinition' {} Maybe DeviceDefinitionVersion
a -> CreateDeviceDefinition
s {$sel:initialVersion:CreateDeviceDefinition' :: Maybe DeviceDefinitionVersion
initialVersion = Maybe DeviceDefinitionVersion
a} :: CreateDeviceDefinition)

-- | The name of the device definition.
createDeviceDefinition_name :: Lens.Lens' CreateDeviceDefinition (Prelude.Maybe Prelude.Text)
createDeviceDefinition_name :: Lens' CreateDeviceDefinition (Maybe Text)
createDeviceDefinition_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceDefinition' {Maybe Text
name :: Maybe Text
$sel:name:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe Text
name} -> Maybe Text
name) (\s :: CreateDeviceDefinition
s@CreateDeviceDefinition' {} Maybe Text
a -> CreateDeviceDefinition
s {$sel:name:CreateDeviceDefinition' :: Maybe Text
name = Maybe Text
a} :: CreateDeviceDefinition)

-- | Tag(s) to add to the new resource.
createDeviceDefinition_tags :: Lens.Lens' CreateDeviceDefinition (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createDeviceDefinition_tags :: Lens' CreateDeviceDefinition (Maybe (HashMap Text Text))
createDeviceDefinition_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceDefinition' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateDeviceDefinition
s@CreateDeviceDefinition' {} Maybe (HashMap Text Text)
a -> CreateDeviceDefinition
s {$sel:tags:CreateDeviceDefinition' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateDeviceDefinition) 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

instance Core.AWSRequest CreateDeviceDefinition where
  type
    AWSResponse CreateDeviceDefinition =
      CreateDeviceDefinitionResponse
  request :: (Service -> Service)
-> CreateDeviceDefinition -> Request CreateDeviceDefinition
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 CreateDeviceDefinition
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateDeviceDefinition)))
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 Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> CreateDeviceDefinitionResponse
CreateDeviceDefinitionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreationTimestamp")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LastUpdatedTimestamp")
            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
"LatestVersion")
            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
"LatestVersionArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateDeviceDefinition where
  hashWithSalt :: Int -> CreateDeviceDefinition -> Int
hashWithSalt Int
_salt CreateDeviceDefinition' {Maybe Text
Maybe (HashMap Text Text)
Maybe DeviceDefinitionVersion
tags :: Maybe (HashMap Text Text)
name :: Maybe Text
initialVersion :: Maybe DeviceDefinitionVersion
amznClientToken :: Maybe Text
$sel:tags:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe (HashMap Text Text)
$sel:name:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe Text
$sel:initialVersion:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe DeviceDefinitionVersion
$sel:amznClientToken:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
amznClientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeviceDefinitionVersion
initialVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags

instance Prelude.NFData CreateDeviceDefinition where
  rnf :: CreateDeviceDefinition -> ()
rnf CreateDeviceDefinition' {Maybe Text
Maybe (HashMap Text Text)
Maybe DeviceDefinitionVersion
tags :: Maybe (HashMap Text Text)
name :: Maybe Text
initialVersion :: Maybe DeviceDefinitionVersion
amznClientToken :: Maybe Text
$sel:tags:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe (HashMap Text Text)
$sel:name:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe Text
$sel:initialVersion:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe DeviceDefinitionVersion
$sel:amznClientToken:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
amznClientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeviceDefinitionVersion
initialVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags

instance Data.ToHeaders CreateDeviceDefinition where
  toHeaders :: CreateDeviceDefinition -> ResponseHeaders
toHeaders CreateDeviceDefinition' {Maybe Text
Maybe (HashMap Text Text)
Maybe DeviceDefinitionVersion
tags :: Maybe (HashMap Text Text)
name :: Maybe Text
initialVersion :: Maybe DeviceDefinitionVersion
amznClientToken :: Maybe Text
$sel:tags:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe (HashMap Text Text)
$sel:name:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe Text
$sel:initialVersion:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe DeviceDefinitionVersion
$sel:amznClientToken:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"X-Amzn-Client-Token" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
amznClientToken,
        HeaderName
"Content-Type"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/x-amz-json-1.1" :: Prelude.ByteString)
      ]

instance Data.ToJSON CreateDeviceDefinition where
  toJSON :: CreateDeviceDefinition -> Value
toJSON CreateDeviceDefinition' {Maybe Text
Maybe (HashMap Text Text)
Maybe DeviceDefinitionVersion
tags :: Maybe (HashMap Text Text)
name :: Maybe Text
initialVersion :: Maybe DeviceDefinitionVersion
amznClientToken :: Maybe Text
$sel:tags:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe (HashMap Text Text)
$sel:name:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe Text
$sel:initialVersion:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe DeviceDefinitionVersion
$sel:amznClientToken:CreateDeviceDefinition' :: CreateDeviceDefinition -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"InitialVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DeviceDefinitionVersion
initialVersion,
            (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
name,
            (Key
"tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
tags
          ]
      )

instance Data.ToPath CreateDeviceDefinition where
  toPath :: CreateDeviceDefinition -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/greengrass/definition/devices"

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

-- | /See:/ 'newCreateDeviceDefinitionResponse' smart constructor.
data CreateDeviceDefinitionResponse = CreateDeviceDefinitionResponse'
  { -- | The ARN of the definition.
    CreateDeviceDefinitionResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The time, in milliseconds since the epoch, when the definition was
    -- created.
    CreateDeviceDefinitionResponse -> Maybe Text
creationTimestamp :: Prelude.Maybe Prelude.Text,
    -- | The ID of the definition.
    CreateDeviceDefinitionResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The time, in milliseconds since the epoch, when the definition was last
    -- updated.
    CreateDeviceDefinitionResponse -> Maybe Text
lastUpdatedTimestamp :: Prelude.Maybe Prelude.Text,
    -- | The ID of the latest version associated with the definition.
    CreateDeviceDefinitionResponse -> Maybe Text
latestVersion :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the latest version associated with the definition.
    CreateDeviceDefinitionResponse -> Maybe Text
latestVersionArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the definition.
    CreateDeviceDefinitionResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateDeviceDefinitionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateDeviceDefinitionResponse
-> CreateDeviceDefinitionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDeviceDefinitionResponse
-> CreateDeviceDefinitionResponse -> Bool
$c/= :: CreateDeviceDefinitionResponse
-> CreateDeviceDefinitionResponse -> Bool
== :: CreateDeviceDefinitionResponse
-> CreateDeviceDefinitionResponse -> Bool
$c== :: CreateDeviceDefinitionResponse
-> CreateDeviceDefinitionResponse -> Bool
Prelude.Eq, ReadPrec [CreateDeviceDefinitionResponse]
ReadPrec CreateDeviceDefinitionResponse
Int -> ReadS CreateDeviceDefinitionResponse
ReadS [CreateDeviceDefinitionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDeviceDefinitionResponse]
$creadListPrec :: ReadPrec [CreateDeviceDefinitionResponse]
readPrec :: ReadPrec CreateDeviceDefinitionResponse
$creadPrec :: ReadPrec CreateDeviceDefinitionResponse
readList :: ReadS [CreateDeviceDefinitionResponse]
$creadList :: ReadS [CreateDeviceDefinitionResponse]
readsPrec :: Int -> ReadS CreateDeviceDefinitionResponse
$creadsPrec :: Int -> ReadS CreateDeviceDefinitionResponse
Prelude.Read, Int -> CreateDeviceDefinitionResponse -> ShowS
[CreateDeviceDefinitionResponse] -> ShowS
CreateDeviceDefinitionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDeviceDefinitionResponse] -> ShowS
$cshowList :: [CreateDeviceDefinitionResponse] -> ShowS
show :: CreateDeviceDefinitionResponse -> String
$cshow :: CreateDeviceDefinitionResponse -> String
showsPrec :: Int -> CreateDeviceDefinitionResponse -> ShowS
$cshowsPrec :: Int -> CreateDeviceDefinitionResponse -> ShowS
Prelude.Show, forall x.
Rep CreateDeviceDefinitionResponse x
-> CreateDeviceDefinitionResponse
forall x.
CreateDeviceDefinitionResponse
-> Rep CreateDeviceDefinitionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateDeviceDefinitionResponse x
-> CreateDeviceDefinitionResponse
$cfrom :: forall x.
CreateDeviceDefinitionResponse
-> Rep CreateDeviceDefinitionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateDeviceDefinitionResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'arn', 'createDeviceDefinitionResponse_arn' - The ARN of the definition.
--
-- 'creationTimestamp', 'createDeviceDefinitionResponse_creationTimestamp' - The time, in milliseconds since the epoch, when the definition was
-- created.
--
-- 'id', 'createDeviceDefinitionResponse_id' - The ID of the definition.
--
-- 'lastUpdatedTimestamp', 'createDeviceDefinitionResponse_lastUpdatedTimestamp' - The time, in milliseconds since the epoch, when the definition was last
-- updated.
--
-- 'latestVersion', 'createDeviceDefinitionResponse_latestVersion' - The ID of the latest version associated with the definition.
--
-- 'latestVersionArn', 'createDeviceDefinitionResponse_latestVersionArn' - The ARN of the latest version associated with the definition.
--
-- 'name', 'createDeviceDefinitionResponse_name' - The name of the definition.
--
-- 'httpStatus', 'createDeviceDefinitionResponse_httpStatus' - The response's http status code.
newCreateDeviceDefinitionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateDeviceDefinitionResponse
newCreateDeviceDefinitionResponse :: Int -> CreateDeviceDefinitionResponse
newCreateDeviceDefinitionResponse Int
pHttpStatus_ =
  CreateDeviceDefinitionResponse'
    { $sel:arn:CreateDeviceDefinitionResponse' :: Maybe Text
arn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTimestamp:CreateDeviceDefinitionResponse' :: Maybe Text
creationTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:id:CreateDeviceDefinitionResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedTimestamp:CreateDeviceDefinitionResponse' :: Maybe Text
lastUpdatedTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:latestVersion:CreateDeviceDefinitionResponse' :: Maybe Text
latestVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:latestVersionArn:CreateDeviceDefinitionResponse' :: Maybe Text
latestVersionArn = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateDeviceDefinitionResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateDeviceDefinitionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | The time, in milliseconds since the epoch, when the definition was
-- created.
createDeviceDefinitionResponse_creationTimestamp :: Lens.Lens' CreateDeviceDefinitionResponse (Prelude.Maybe Prelude.Text)
createDeviceDefinitionResponse_creationTimestamp :: Lens' CreateDeviceDefinitionResponse (Maybe Text)
createDeviceDefinitionResponse_creationTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceDefinitionResponse' {Maybe Text
creationTimestamp :: Maybe Text
$sel:creationTimestamp:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
creationTimestamp} -> Maybe Text
creationTimestamp) (\s :: CreateDeviceDefinitionResponse
s@CreateDeviceDefinitionResponse' {} Maybe Text
a -> CreateDeviceDefinitionResponse
s {$sel:creationTimestamp:CreateDeviceDefinitionResponse' :: Maybe Text
creationTimestamp = Maybe Text
a} :: CreateDeviceDefinitionResponse)

-- | The ID of the definition.
createDeviceDefinitionResponse_id :: Lens.Lens' CreateDeviceDefinitionResponse (Prelude.Maybe Prelude.Text)
createDeviceDefinitionResponse_id :: Lens' CreateDeviceDefinitionResponse (Maybe Text)
createDeviceDefinitionResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceDefinitionResponse' {Maybe Text
id :: Maybe Text
$sel:id:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: CreateDeviceDefinitionResponse
s@CreateDeviceDefinitionResponse' {} Maybe Text
a -> CreateDeviceDefinitionResponse
s {$sel:id:CreateDeviceDefinitionResponse' :: Maybe Text
id = Maybe Text
a} :: CreateDeviceDefinitionResponse)

-- | The time, in milliseconds since the epoch, when the definition was last
-- updated.
createDeviceDefinitionResponse_lastUpdatedTimestamp :: Lens.Lens' CreateDeviceDefinitionResponse (Prelude.Maybe Prelude.Text)
createDeviceDefinitionResponse_lastUpdatedTimestamp :: Lens' CreateDeviceDefinitionResponse (Maybe Text)
createDeviceDefinitionResponse_lastUpdatedTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceDefinitionResponse' {Maybe Text
lastUpdatedTimestamp :: Maybe Text
$sel:lastUpdatedTimestamp:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
lastUpdatedTimestamp} -> Maybe Text
lastUpdatedTimestamp) (\s :: CreateDeviceDefinitionResponse
s@CreateDeviceDefinitionResponse' {} Maybe Text
a -> CreateDeviceDefinitionResponse
s {$sel:lastUpdatedTimestamp:CreateDeviceDefinitionResponse' :: Maybe Text
lastUpdatedTimestamp = Maybe Text
a} :: CreateDeviceDefinitionResponse)

-- | The ID of the latest version associated with the definition.
createDeviceDefinitionResponse_latestVersion :: Lens.Lens' CreateDeviceDefinitionResponse (Prelude.Maybe Prelude.Text)
createDeviceDefinitionResponse_latestVersion :: Lens' CreateDeviceDefinitionResponse (Maybe Text)
createDeviceDefinitionResponse_latestVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceDefinitionResponse' {Maybe Text
latestVersion :: Maybe Text
$sel:latestVersion:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
latestVersion} -> Maybe Text
latestVersion) (\s :: CreateDeviceDefinitionResponse
s@CreateDeviceDefinitionResponse' {} Maybe Text
a -> CreateDeviceDefinitionResponse
s {$sel:latestVersion:CreateDeviceDefinitionResponse' :: Maybe Text
latestVersion = Maybe Text
a} :: CreateDeviceDefinitionResponse)

-- | The ARN of the latest version associated with the definition.
createDeviceDefinitionResponse_latestVersionArn :: Lens.Lens' CreateDeviceDefinitionResponse (Prelude.Maybe Prelude.Text)
createDeviceDefinitionResponse_latestVersionArn :: Lens' CreateDeviceDefinitionResponse (Maybe Text)
createDeviceDefinitionResponse_latestVersionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceDefinitionResponse' {Maybe Text
latestVersionArn :: Maybe Text
$sel:latestVersionArn:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
latestVersionArn} -> Maybe Text
latestVersionArn) (\s :: CreateDeviceDefinitionResponse
s@CreateDeviceDefinitionResponse' {} Maybe Text
a -> CreateDeviceDefinitionResponse
s {$sel:latestVersionArn:CreateDeviceDefinitionResponse' :: Maybe Text
latestVersionArn = Maybe Text
a} :: CreateDeviceDefinitionResponse)

-- | The name of the definition.
createDeviceDefinitionResponse_name :: Lens.Lens' CreateDeviceDefinitionResponse (Prelude.Maybe Prelude.Text)
createDeviceDefinitionResponse_name :: Lens' CreateDeviceDefinitionResponse (Maybe Text)
createDeviceDefinitionResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceDefinitionResponse' {Maybe Text
name :: Maybe Text
$sel:name:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: CreateDeviceDefinitionResponse
s@CreateDeviceDefinitionResponse' {} Maybe Text
a -> CreateDeviceDefinitionResponse
s {$sel:name:CreateDeviceDefinitionResponse' :: Maybe Text
name = Maybe Text
a} :: CreateDeviceDefinitionResponse)

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

instance
  Prelude.NFData
    CreateDeviceDefinitionResponse
  where
  rnf :: CreateDeviceDefinitionResponse -> ()
rnf CreateDeviceDefinitionResponse' {Int
Maybe Text
httpStatus :: Int
name :: Maybe Text
latestVersionArn :: Maybe Text
latestVersion :: Maybe Text
lastUpdatedTimestamp :: Maybe Text
id :: Maybe Text
creationTimestamp :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Int
$sel:name:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
$sel:latestVersionArn:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
$sel:latestVersion:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
$sel:lastUpdatedTimestamp:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
$sel:id:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
$sel:creationTimestamp:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
$sel:arn:CreateDeviceDefinitionResponse' :: CreateDeviceDefinitionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
creationTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastUpdatedTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
latestVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
latestVersionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus