{-# 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.IoTWireless.CreateDeviceProfile
-- 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 new device profile.
module Amazonka.IoTWireless.CreateDeviceProfile
  ( -- * Creating a Request
    CreateDeviceProfile (..),
    newCreateDeviceProfile,

    -- * Request Lenses
    createDeviceProfile_clientRequestToken,
    createDeviceProfile_loRaWAN,
    createDeviceProfile_name,
    createDeviceProfile_tags,

    -- * Destructuring the Response
    CreateDeviceProfileResponse (..),
    newCreateDeviceProfileResponse,

    -- * Response Lenses
    createDeviceProfileResponse_arn,
    createDeviceProfileResponse_id,
    createDeviceProfileResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateDeviceProfile' smart constructor.
data CreateDeviceProfile = CreateDeviceProfile'
  { -- | Each resource must have a unique client request token. If you try to
    -- create a new resource with the same token as a resource that already
    -- exists, an exception occurs. If you omit this value, AWS SDKs will
    -- automatically generate a unique client request.
    CreateDeviceProfile -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The device profile information to use to create the device profile.
    CreateDeviceProfile -> Maybe LoRaWANDeviceProfile
loRaWAN :: Prelude.Maybe LoRaWANDeviceProfile,
    -- | The name of the new resource.
    CreateDeviceProfile -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The tags to attach to the new device profile. Tags are metadata that you
    -- can use to manage a resource.
    CreateDeviceProfile -> Maybe [Tag]
tags :: Prelude.Maybe [Tag]
  }
  deriving (CreateDeviceProfile -> CreateDeviceProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDeviceProfile -> CreateDeviceProfile -> Bool
$c/= :: CreateDeviceProfile -> CreateDeviceProfile -> Bool
== :: CreateDeviceProfile -> CreateDeviceProfile -> Bool
$c== :: CreateDeviceProfile -> CreateDeviceProfile -> Bool
Prelude.Eq, ReadPrec [CreateDeviceProfile]
ReadPrec CreateDeviceProfile
Int -> ReadS CreateDeviceProfile
ReadS [CreateDeviceProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDeviceProfile]
$creadListPrec :: ReadPrec [CreateDeviceProfile]
readPrec :: ReadPrec CreateDeviceProfile
$creadPrec :: ReadPrec CreateDeviceProfile
readList :: ReadS [CreateDeviceProfile]
$creadList :: ReadS [CreateDeviceProfile]
readsPrec :: Int -> ReadS CreateDeviceProfile
$creadsPrec :: Int -> ReadS CreateDeviceProfile
Prelude.Read, Int -> CreateDeviceProfile -> ShowS
[CreateDeviceProfile] -> ShowS
CreateDeviceProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDeviceProfile] -> ShowS
$cshowList :: [CreateDeviceProfile] -> ShowS
show :: CreateDeviceProfile -> String
$cshow :: CreateDeviceProfile -> String
showsPrec :: Int -> CreateDeviceProfile -> ShowS
$cshowsPrec :: Int -> CreateDeviceProfile -> ShowS
Prelude.Show, forall x. Rep CreateDeviceProfile x -> CreateDeviceProfile
forall x. CreateDeviceProfile -> Rep CreateDeviceProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateDeviceProfile x -> CreateDeviceProfile
$cfrom :: forall x. CreateDeviceProfile -> Rep CreateDeviceProfile x
Prelude.Generic)

-- |
-- Create a value of 'CreateDeviceProfile' 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:
--
-- 'clientRequestToken', 'createDeviceProfile_clientRequestToken' - Each resource must have a unique client request token. If you try to
-- create a new resource with the same token as a resource that already
-- exists, an exception occurs. If you omit this value, AWS SDKs will
-- automatically generate a unique client request.
--
-- 'loRaWAN', 'createDeviceProfile_loRaWAN' - The device profile information to use to create the device profile.
--
-- 'name', 'createDeviceProfile_name' - The name of the new resource.
--
-- 'tags', 'createDeviceProfile_tags' - The tags to attach to the new device profile. Tags are metadata that you
-- can use to manage a resource.
newCreateDeviceProfile ::
  CreateDeviceProfile
newCreateDeviceProfile :: CreateDeviceProfile
newCreateDeviceProfile =
  CreateDeviceProfile'
    { $sel:clientRequestToken:CreateDeviceProfile' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:loRaWAN:CreateDeviceProfile' :: Maybe LoRaWANDeviceProfile
loRaWAN = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateDeviceProfile' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateDeviceProfile' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing
    }

-- | Each resource must have a unique client request token. If you try to
-- create a new resource with the same token as a resource that already
-- exists, an exception occurs. If you omit this value, AWS SDKs will
-- automatically generate a unique client request.
createDeviceProfile_clientRequestToken :: Lens.Lens' CreateDeviceProfile (Prelude.Maybe Prelude.Text)
createDeviceProfile_clientRequestToken :: Lens' CreateDeviceProfile (Maybe Text)
createDeviceProfile_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceProfile' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: CreateDeviceProfile
s@CreateDeviceProfile' {} Maybe Text
a -> CreateDeviceProfile
s {$sel:clientRequestToken:CreateDeviceProfile' :: Maybe Text
clientRequestToken = Maybe Text
a} :: CreateDeviceProfile)

-- | The device profile information to use to create the device profile.
createDeviceProfile_loRaWAN :: Lens.Lens' CreateDeviceProfile (Prelude.Maybe LoRaWANDeviceProfile)
createDeviceProfile_loRaWAN :: Lens' CreateDeviceProfile (Maybe LoRaWANDeviceProfile)
createDeviceProfile_loRaWAN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceProfile' {Maybe LoRaWANDeviceProfile
loRaWAN :: Maybe LoRaWANDeviceProfile
$sel:loRaWAN:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe LoRaWANDeviceProfile
loRaWAN} -> Maybe LoRaWANDeviceProfile
loRaWAN) (\s :: CreateDeviceProfile
s@CreateDeviceProfile' {} Maybe LoRaWANDeviceProfile
a -> CreateDeviceProfile
s {$sel:loRaWAN:CreateDeviceProfile' :: Maybe LoRaWANDeviceProfile
loRaWAN = Maybe LoRaWANDeviceProfile
a} :: CreateDeviceProfile)

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

-- | The tags to attach to the new device profile. Tags are metadata that you
-- can use to manage a resource.
createDeviceProfile_tags :: Lens.Lens' CreateDeviceProfile (Prelude.Maybe [Tag])
createDeviceProfile_tags :: Lens' CreateDeviceProfile (Maybe [Tag])
createDeviceProfile_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceProfile' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateDeviceProfile
s@CreateDeviceProfile' {} Maybe [Tag]
a -> CreateDeviceProfile
s {$sel:tags:CreateDeviceProfile' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateDeviceProfile) 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 CreateDeviceProfile where
  type
    AWSResponse CreateDeviceProfile =
      CreateDeviceProfileResponse
  request :: (Service -> Service)
-> CreateDeviceProfile -> Request CreateDeviceProfile
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 CreateDeviceProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateDeviceProfile)))
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 -> CreateDeviceProfileResponse
CreateDeviceProfileResponse'
            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
"Id")
            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 CreateDeviceProfile where
  hashWithSalt :: Int -> CreateDeviceProfile -> Int
hashWithSalt Int
_salt CreateDeviceProfile' {Maybe [Tag]
Maybe Text
Maybe LoRaWANDeviceProfile
tags :: Maybe [Tag]
name :: Maybe Text
loRaWAN :: Maybe LoRaWANDeviceProfile
clientRequestToken :: Maybe Text
$sel:tags:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe [Tag]
$sel:name:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe Text
$sel:loRaWAN:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe LoRaWANDeviceProfile
$sel:clientRequestToken:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LoRaWANDeviceProfile
loRaWAN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags

instance Prelude.NFData CreateDeviceProfile where
  rnf :: CreateDeviceProfile -> ()
rnf CreateDeviceProfile' {Maybe [Tag]
Maybe Text
Maybe LoRaWANDeviceProfile
tags :: Maybe [Tag]
name :: Maybe Text
loRaWAN :: Maybe LoRaWANDeviceProfile
clientRequestToken :: Maybe Text
$sel:tags:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe [Tag]
$sel:name:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe Text
$sel:loRaWAN:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe LoRaWANDeviceProfile
$sel:clientRequestToken:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LoRaWANDeviceProfile
loRaWAN
      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 [Tag]
tags

instance Data.ToHeaders CreateDeviceProfile where
  toHeaders :: CreateDeviceProfile -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON CreateDeviceProfile where
  toJSON :: CreateDeviceProfile -> Value
toJSON CreateDeviceProfile' {Maybe [Tag]
Maybe Text
Maybe LoRaWANDeviceProfile
tags :: Maybe [Tag]
name :: Maybe Text
loRaWAN :: Maybe LoRaWANDeviceProfile
clientRequestToken :: Maybe Text
$sel:tags:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe [Tag]
$sel:name:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe Text
$sel:loRaWAN:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe LoRaWANDeviceProfile
$sel:clientRequestToken:CreateDeviceProfile' :: CreateDeviceProfile -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientRequestToken" 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
clientRequestToken,
            (Key
"LoRaWAN" 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 LoRaWANDeviceProfile
loRaWAN,
            (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 [Tag]
tags
          ]
      )

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

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

-- | /See:/ 'newCreateDeviceProfileResponse' smart constructor.
data CreateDeviceProfileResponse = CreateDeviceProfileResponse'
  { -- | The Amazon Resource Name of the new resource.
    CreateDeviceProfileResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the new device profile.
    CreateDeviceProfileResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateDeviceProfileResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateDeviceProfileResponse -> CreateDeviceProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDeviceProfileResponse -> CreateDeviceProfileResponse -> Bool
$c/= :: CreateDeviceProfileResponse -> CreateDeviceProfileResponse -> Bool
== :: CreateDeviceProfileResponse -> CreateDeviceProfileResponse -> Bool
$c== :: CreateDeviceProfileResponse -> CreateDeviceProfileResponse -> Bool
Prelude.Eq, ReadPrec [CreateDeviceProfileResponse]
ReadPrec CreateDeviceProfileResponse
Int -> ReadS CreateDeviceProfileResponse
ReadS [CreateDeviceProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDeviceProfileResponse]
$creadListPrec :: ReadPrec [CreateDeviceProfileResponse]
readPrec :: ReadPrec CreateDeviceProfileResponse
$creadPrec :: ReadPrec CreateDeviceProfileResponse
readList :: ReadS [CreateDeviceProfileResponse]
$creadList :: ReadS [CreateDeviceProfileResponse]
readsPrec :: Int -> ReadS CreateDeviceProfileResponse
$creadsPrec :: Int -> ReadS CreateDeviceProfileResponse
Prelude.Read, Int -> CreateDeviceProfileResponse -> ShowS
[CreateDeviceProfileResponse] -> ShowS
CreateDeviceProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDeviceProfileResponse] -> ShowS
$cshowList :: [CreateDeviceProfileResponse] -> ShowS
show :: CreateDeviceProfileResponse -> String
$cshow :: CreateDeviceProfileResponse -> String
showsPrec :: Int -> CreateDeviceProfileResponse -> ShowS
$cshowsPrec :: Int -> CreateDeviceProfileResponse -> ShowS
Prelude.Show, forall x.
Rep CreateDeviceProfileResponse x -> CreateDeviceProfileResponse
forall x.
CreateDeviceProfileResponse -> Rep CreateDeviceProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateDeviceProfileResponse x -> CreateDeviceProfileResponse
$cfrom :: forall x.
CreateDeviceProfileResponse -> Rep CreateDeviceProfileResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateDeviceProfileResponse' 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', 'createDeviceProfileResponse_arn' - The Amazon Resource Name of the new resource.
--
-- 'id', 'createDeviceProfileResponse_id' - The ID of the new device profile.
--
-- 'httpStatus', 'createDeviceProfileResponse_httpStatus' - The response's http status code.
newCreateDeviceProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateDeviceProfileResponse
newCreateDeviceProfileResponse :: Int -> CreateDeviceProfileResponse
newCreateDeviceProfileResponse Int
pHttpStatus_ =
  CreateDeviceProfileResponse'
    { $sel:arn:CreateDeviceProfileResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:id:CreateDeviceProfileResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateDeviceProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name of the new resource.
createDeviceProfileResponse_arn :: Lens.Lens' CreateDeviceProfileResponse (Prelude.Maybe Prelude.Text)
createDeviceProfileResponse_arn :: Lens' CreateDeviceProfileResponse (Maybe Text)
createDeviceProfileResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceProfileResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:CreateDeviceProfileResponse' :: CreateDeviceProfileResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: CreateDeviceProfileResponse
s@CreateDeviceProfileResponse' {} Maybe Text
a -> CreateDeviceProfileResponse
s {$sel:arn:CreateDeviceProfileResponse' :: Maybe Text
arn = Maybe Text
a} :: CreateDeviceProfileResponse)

-- | The ID of the new device profile.
createDeviceProfileResponse_id :: Lens.Lens' CreateDeviceProfileResponse (Prelude.Maybe Prelude.Text)
createDeviceProfileResponse_id :: Lens' CreateDeviceProfileResponse (Maybe Text)
createDeviceProfileResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDeviceProfileResponse' {Maybe Text
id :: Maybe Text
$sel:id:CreateDeviceProfileResponse' :: CreateDeviceProfileResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: CreateDeviceProfileResponse
s@CreateDeviceProfileResponse' {} Maybe Text
a -> CreateDeviceProfileResponse
s {$sel:id:CreateDeviceProfileResponse' :: Maybe Text
id = Maybe Text
a} :: CreateDeviceProfileResponse)

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

instance Prelude.NFData CreateDeviceProfileResponse where
  rnf :: CreateDeviceProfileResponse -> ()
rnf CreateDeviceProfileResponse' {Int
Maybe Text
httpStatus :: Int
id :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:CreateDeviceProfileResponse' :: CreateDeviceProfileResponse -> Int
$sel:id:CreateDeviceProfileResponse' :: CreateDeviceProfileResponse -> Maybe Text
$sel:arn:CreateDeviceProfileResponse' :: CreateDeviceProfileResponse -> 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
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus