{-# 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.IoT.UpdateThing
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the data for a thing.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions UpdateThing>
-- action.
module Amazonka.IoT.UpdateThing
  ( -- * Creating a Request
    UpdateThing (..),
    newUpdateThing,

    -- * Request Lenses
    updateThing_attributePayload,
    updateThing_expectedVersion,
    updateThing_removeThingType,
    updateThing_thingTypeName,
    updateThing_thingName,

    -- * Destructuring the Response
    UpdateThingResponse (..),
    newUpdateThingResponse,

    -- * Response Lenses
    updateThingResponse_httpStatus,
  )
where

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

-- | The input for the UpdateThing operation.
--
-- /See:/ 'newUpdateThing' smart constructor.
data UpdateThing = UpdateThing'
  { -- | A list of thing attributes, a JSON string containing name-value pairs.
    -- For example:
    --
    -- @{\\\"attributes\\\":{\\\"name1\\\":\\\"value2\\\"}}@
    --
    -- This data is used to add new attributes or update existing attributes.
    UpdateThing -> Maybe AttributePayload
attributePayload :: Prelude.Maybe AttributePayload,
    -- | The expected version of the thing record in the registry. If the version
    -- of the record in the registry does not match the expected version
    -- specified in the request, the @UpdateThing@ request is rejected with a
    -- @VersionConflictException@.
    UpdateThing -> Maybe Integer
expectedVersion :: Prelude.Maybe Prelude.Integer,
    -- | Remove a thing type association. If __true__, the association is
    -- removed.
    UpdateThing -> Maybe Bool
removeThingType :: Prelude.Maybe Prelude.Bool,
    -- | The name of the thing type.
    UpdateThing -> Maybe Text
thingTypeName :: Prelude.Maybe Prelude.Text,
    -- | The name of the thing to update.
    --
    -- You can\'t change a thing\'s name. To change a thing\'s name, you must
    -- create a new thing, give it the new name, and then delete the old thing.
    UpdateThing -> Text
thingName :: Prelude.Text
  }
  deriving (UpdateThing -> UpdateThing -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateThing -> UpdateThing -> Bool
$c/= :: UpdateThing -> UpdateThing -> Bool
== :: UpdateThing -> UpdateThing -> Bool
$c== :: UpdateThing -> UpdateThing -> Bool
Prelude.Eq, ReadPrec [UpdateThing]
ReadPrec UpdateThing
Int -> ReadS UpdateThing
ReadS [UpdateThing]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateThing]
$creadListPrec :: ReadPrec [UpdateThing]
readPrec :: ReadPrec UpdateThing
$creadPrec :: ReadPrec UpdateThing
readList :: ReadS [UpdateThing]
$creadList :: ReadS [UpdateThing]
readsPrec :: Int -> ReadS UpdateThing
$creadsPrec :: Int -> ReadS UpdateThing
Prelude.Read, Int -> UpdateThing -> ShowS
[UpdateThing] -> ShowS
UpdateThing -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateThing] -> ShowS
$cshowList :: [UpdateThing] -> ShowS
show :: UpdateThing -> String
$cshow :: UpdateThing -> String
showsPrec :: Int -> UpdateThing -> ShowS
$cshowsPrec :: Int -> UpdateThing -> ShowS
Prelude.Show, forall x. Rep UpdateThing x -> UpdateThing
forall x. UpdateThing -> Rep UpdateThing x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateThing x -> UpdateThing
$cfrom :: forall x. UpdateThing -> Rep UpdateThing x
Prelude.Generic)

-- |
-- Create a value of 'UpdateThing' 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:
--
-- 'attributePayload', 'updateThing_attributePayload' - A list of thing attributes, a JSON string containing name-value pairs.
-- For example:
--
-- @{\\\"attributes\\\":{\\\"name1\\\":\\\"value2\\\"}}@
--
-- This data is used to add new attributes or update existing attributes.
--
-- 'expectedVersion', 'updateThing_expectedVersion' - The expected version of the thing record in the registry. If the version
-- of the record in the registry does not match the expected version
-- specified in the request, the @UpdateThing@ request is rejected with a
-- @VersionConflictException@.
--
-- 'removeThingType', 'updateThing_removeThingType' - Remove a thing type association. If __true__, the association is
-- removed.
--
-- 'thingTypeName', 'updateThing_thingTypeName' - The name of the thing type.
--
-- 'thingName', 'updateThing_thingName' - The name of the thing to update.
--
-- You can\'t change a thing\'s name. To change a thing\'s name, you must
-- create a new thing, give it the new name, and then delete the old thing.
newUpdateThing ::
  -- | 'thingName'
  Prelude.Text ->
  UpdateThing
newUpdateThing :: Text -> UpdateThing
newUpdateThing Text
pThingName_ =
  UpdateThing'
    { $sel:attributePayload:UpdateThing' :: Maybe AttributePayload
attributePayload = forall a. Maybe a
Prelude.Nothing,
      $sel:expectedVersion:UpdateThing' :: Maybe Integer
expectedVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:removeThingType:UpdateThing' :: Maybe Bool
removeThingType = forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypeName:UpdateThing' :: Maybe Text
thingTypeName = forall a. Maybe a
Prelude.Nothing,
      $sel:thingName:UpdateThing' :: Text
thingName = Text
pThingName_
    }

-- | A list of thing attributes, a JSON string containing name-value pairs.
-- For example:
--
-- @{\\\"attributes\\\":{\\\"name1\\\":\\\"value2\\\"}}@
--
-- This data is used to add new attributes or update existing attributes.
updateThing_attributePayload :: Lens.Lens' UpdateThing (Prelude.Maybe AttributePayload)
updateThing_attributePayload :: Lens' UpdateThing (Maybe AttributePayload)
updateThing_attributePayload = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThing' {Maybe AttributePayload
attributePayload :: Maybe AttributePayload
$sel:attributePayload:UpdateThing' :: UpdateThing -> Maybe AttributePayload
attributePayload} -> Maybe AttributePayload
attributePayload) (\s :: UpdateThing
s@UpdateThing' {} Maybe AttributePayload
a -> UpdateThing
s {$sel:attributePayload:UpdateThing' :: Maybe AttributePayload
attributePayload = Maybe AttributePayload
a} :: UpdateThing)

-- | The expected version of the thing record in the registry. If the version
-- of the record in the registry does not match the expected version
-- specified in the request, the @UpdateThing@ request is rejected with a
-- @VersionConflictException@.
updateThing_expectedVersion :: Lens.Lens' UpdateThing (Prelude.Maybe Prelude.Integer)
updateThing_expectedVersion :: Lens' UpdateThing (Maybe Integer)
updateThing_expectedVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThing' {Maybe Integer
expectedVersion :: Maybe Integer
$sel:expectedVersion:UpdateThing' :: UpdateThing -> Maybe Integer
expectedVersion} -> Maybe Integer
expectedVersion) (\s :: UpdateThing
s@UpdateThing' {} Maybe Integer
a -> UpdateThing
s {$sel:expectedVersion:UpdateThing' :: Maybe Integer
expectedVersion = Maybe Integer
a} :: UpdateThing)

-- | Remove a thing type association. If __true__, the association is
-- removed.
updateThing_removeThingType :: Lens.Lens' UpdateThing (Prelude.Maybe Prelude.Bool)
updateThing_removeThingType :: Lens' UpdateThing (Maybe Bool)
updateThing_removeThingType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThing' {Maybe Bool
removeThingType :: Maybe Bool
$sel:removeThingType:UpdateThing' :: UpdateThing -> Maybe Bool
removeThingType} -> Maybe Bool
removeThingType) (\s :: UpdateThing
s@UpdateThing' {} Maybe Bool
a -> UpdateThing
s {$sel:removeThingType:UpdateThing' :: Maybe Bool
removeThingType = Maybe Bool
a} :: UpdateThing)

-- | The name of the thing type.
updateThing_thingTypeName :: Lens.Lens' UpdateThing (Prelude.Maybe Prelude.Text)
updateThing_thingTypeName :: Lens' UpdateThing (Maybe Text)
updateThing_thingTypeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThing' {Maybe Text
thingTypeName :: Maybe Text
$sel:thingTypeName:UpdateThing' :: UpdateThing -> Maybe Text
thingTypeName} -> Maybe Text
thingTypeName) (\s :: UpdateThing
s@UpdateThing' {} Maybe Text
a -> UpdateThing
s {$sel:thingTypeName:UpdateThing' :: Maybe Text
thingTypeName = Maybe Text
a} :: UpdateThing)

-- | The name of the thing to update.
--
-- You can\'t change a thing\'s name. To change a thing\'s name, you must
-- create a new thing, give it the new name, and then delete the old thing.
updateThing_thingName :: Lens.Lens' UpdateThing Prelude.Text
updateThing_thingName :: Lens' UpdateThing Text
updateThing_thingName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThing' {Text
thingName :: Text
$sel:thingName:UpdateThing' :: UpdateThing -> Text
thingName} -> Text
thingName) (\s :: UpdateThing
s@UpdateThing' {} Text
a -> UpdateThing
s {$sel:thingName:UpdateThing' :: Text
thingName = Text
a} :: UpdateThing)

instance Core.AWSRequest UpdateThing where
  type AWSResponse UpdateThing = UpdateThingResponse
  request :: (Service -> Service) -> UpdateThing -> Request UpdateThing
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateThing
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateThing)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> UpdateThingResponse
UpdateThingResponse'
            forall (f :: * -> *) a b. Functor 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 UpdateThing where
  hashWithSalt :: Int -> UpdateThing -> Int
hashWithSalt Int
_salt UpdateThing' {Maybe Bool
Maybe Integer
Maybe Text
Maybe AttributePayload
Text
thingName :: Text
thingTypeName :: Maybe Text
removeThingType :: Maybe Bool
expectedVersion :: Maybe Integer
attributePayload :: Maybe AttributePayload
$sel:thingName:UpdateThing' :: UpdateThing -> Text
$sel:thingTypeName:UpdateThing' :: UpdateThing -> Maybe Text
$sel:removeThingType:UpdateThing' :: UpdateThing -> Maybe Bool
$sel:expectedVersion:UpdateThing' :: UpdateThing -> Maybe Integer
$sel:attributePayload:UpdateThing' :: UpdateThing -> Maybe AttributePayload
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AttributePayload
attributePayload
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
expectedVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
removeThingType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
thingTypeName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingName

instance Prelude.NFData UpdateThing where
  rnf :: UpdateThing -> ()
rnf UpdateThing' {Maybe Bool
Maybe Integer
Maybe Text
Maybe AttributePayload
Text
thingName :: Text
thingTypeName :: Maybe Text
removeThingType :: Maybe Bool
expectedVersion :: Maybe Integer
attributePayload :: Maybe AttributePayload
$sel:thingName:UpdateThing' :: UpdateThing -> Text
$sel:thingTypeName:UpdateThing' :: UpdateThing -> Maybe Text
$sel:removeThingType:UpdateThing' :: UpdateThing -> Maybe Bool
$sel:expectedVersion:UpdateThing' :: UpdateThing -> Maybe Integer
$sel:attributePayload:UpdateThing' :: UpdateThing -> Maybe AttributePayload
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AttributePayload
attributePayload
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
expectedVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
removeThingType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
thingTypeName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
thingName

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

instance Data.ToJSON UpdateThing where
  toJSON :: UpdateThing -> Value
toJSON UpdateThing' {Maybe Bool
Maybe Integer
Maybe Text
Maybe AttributePayload
Text
thingName :: Text
thingTypeName :: Maybe Text
removeThingType :: Maybe Bool
expectedVersion :: Maybe Integer
attributePayload :: Maybe AttributePayload
$sel:thingName:UpdateThing' :: UpdateThing -> Text
$sel:thingTypeName:UpdateThing' :: UpdateThing -> Maybe Text
$sel:removeThingType:UpdateThing' :: UpdateThing -> Maybe Bool
$sel:expectedVersion:UpdateThing' :: UpdateThing -> Maybe Integer
$sel:attributePayload:UpdateThing' :: UpdateThing -> Maybe AttributePayload
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"attributePayload" 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 AttributePayload
attributePayload,
            (Key
"expectedVersion" 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 Integer
expectedVersion,
            (Key
"removeThingType" 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 Bool
removeThingType,
            (Key
"thingTypeName" 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
thingTypeName
          ]
      )

instance Data.ToPath UpdateThing where
  toPath :: UpdateThing -> ByteString
toPath UpdateThing' {Maybe Bool
Maybe Integer
Maybe Text
Maybe AttributePayload
Text
thingName :: Text
thingTypeName :: Maybe Text
removeThingType :: Maybe Bool
expectedVersion :: Maybe Integer
attributePayload :: Maybe AttributePayload
$sel:thingName:UpdateThing' :: UpdateThing -> Text
$sel:thingTypeName:UpdateThing' :: UpdateThing -> Maybe Text
$sel:removeThingType:UpdateThing' :: UpdateThing -> Maybe Bool
$sel:expectedVersion:UpdateThing' :: UpdateThing -> Maybe Integer
$sel:attributePayload:UpdateThing' :: UpdateThing -> Maybe AttributePayload
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/things/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
thingName]

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

-- | The output from the UpdateThing operation.
--
-- /See:/ 'newUpdateThingResponse' smart constructor.
data UpdateThingResponse = UpdateThingResponse'
  { -- | The response's http status code.
    UpdateThingResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateThingResponse -> UpdateThingResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateThingResponse -> UpdateThingResponse -> Bool
$c/= :: UpdateThingResponse -> UpdateThingResponse -> Bool
== :: UpdateThingResponse -> UpdateThingResponse -> Bool
$c== :: UpdateThingResponse -> UpdateThingResponse -> Bool
Prelude.Eq, ReadPrec [UpdateThingResponse]
ReadPrec UpdateThingResponse
Int -> ReadS UpdateThingResponse
ReadS [UpdateThingResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateThingResponse]
$creadListPrec :: ReadPrec [UpdateThingResponse]
readPrec :: ReadPrec UpdateThingResponse
$creadPrec :: ReadPrec UpdateThingResponse
readList :: ReadS [UpdateThingResponse]
$creadList :: ReadS [UpdateThingResponse]
readsPrec :: Int -> ReadS UpdateThingResponse
$creadsPrec :: Int -> ReadS UpdateThingResponse
Prelude.Read, Int -> UpdateThingResponse -> ShowS
[UpdateThingResponse] -> ShowS
UpdateThingResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateThingResponse] -> ShowS
$cshowList :: [UpdateThingResponse] -> ShowS
show :: UpdateThingResponse -> String
$cshow :: UpdateThingResponse -> String
showsPrec :: Int -> UpdateThingResponse -> ShowS
$cshowsPrec :: Int -> UpdateThingResponse -> ShowS
Prelude.Show, forall x. Rep UpdateThingResponse x -> UpdateThingResponse
forall x. UpdateThingResponse -> Rep UpdateThingResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateThingResponse x -> UpdateThingResponse
$cfrom :: forall x. UpdateThingResponse -> Rep UpdateThingResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateThingResponse' 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:
--
-- 'httpStatus', 'updateThingResponse_httpStatus' - The response's http status code.
newUpdateThingResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateThingResponse
newUpdateThingResponse :: Int -> UpdateThingResponse
newUpdateThingResponse Int
pHttpStatus_ =
  UpdateThingResponse' {$sel:httpStatus:UpdateThingResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData UpdateThingResponse where
  rnf :: UpdateThingResponse -> ()
rnf UpdateThingResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateThingResponse' :: UpdateThingResponse -> Int
..} = forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus