{-# 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.UpdateDeviceDefinition
-- 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 a device definition.
module Amazonka.Greengrass.UpdateDeviceDefinition
  ( -- * Creating a Request
    UpdateDeviceDefinition (..),
    newUpdateDeviceDefinition,

    -- * Request Lenses
    updateDeviceDefinition_name,
    updateDeviceDefinition_deviceDefinitionId,

    -- * Destructuring the Response
    UpdateDeviceDefinitionResponse (..),
    newUpdateDeviceDefinitionResponse,

    -- * Response Lenses
    updateDeviceDefinitionResponse_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:/ 'newUpdateDeviceDefinition' smart constructor.
data UpdateDeviceDefinition = UpdateDeviceDefinition'
  { -- | The name of the definition.
    UpdateDeviceDefinition -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The ID of the device definition.
    UpdateDeviceDefinition -> Text
deviceDefinitionId :: Prelude.Text
  }
  deriving (UpdateDeviceDefinition -> UpdateDeviceDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateDeviceDefinition -> UpdateDeviceDefinition -> Bool
$c/= :: UpdateDeviceDefinition -> UpdateDeviceDefinition -> Bool
== :: UpdateDeviceDefinition -> UpdateDeviceDefinition -> Bool
$c== :: UpdateDeviceDefinition -> UpdateDeviceDefinition -> Bool
Prelude.Eq, ReadPrec [UpdateDeviceDefinition]
ReadPrec UpdateDeviceDefinition
Int -> ReadS UpdateDeviceDefinition
ReadS [UpdateDeviceDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateDeviceDefinition]
$creadListPrec :: ReadPrec [UpdateDeviceDefinition]
readPrec :: ReadPrec UpdateDeviceDefinition
$creadPrec :: ReadPrec UpdateDeviceDefinition
readList :: ReadS [UpdateDeviceDefinition]
$creadList :: ReadS [UpdateDeviceDefinition]
readsPrec :: Int -> ReadS UpdateDeviceDefinition
$creadsPrec :: Int -> ReadS UpdateDeviceDefinition
Prelude.Read, Int -> UpdateDeviceDefinition -> ShowS
[UpdateDeviceDefinition] -> ShowS
UpdateDeviceDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateDeviceDefinition] -> ShowS
$cshowList :: [UpdateDeviceDefinition] -> ShowS
show :: UpdateDeviceDefinition -> String
$cshow :: UpdateDeviceDefinition -> String
showsPrec :: Int -> UpdateDeviceDefinition -> ShowS
$cshowsPrec :: Int -> UpdateDeviceDefinition -> ShowS
Prelude.Show, forall x. Rep UpdateDeviceDefinition x -> UpdateDeviceDefinition
forall x. UpdateDeviceDefinition -> Rep UpdateDeviceDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateDeviceDefinition x -> UpdateDeviceDefinition
$cfrom :: forall x. UpdateDeviceDefinition -> Rep UpdateDeviceDefinition x
Prelude.Generic)

-- |
-- Create a value of 'UpdateDeviceDefinition' 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', 'updateDeviceDefinition_name' - The name of the definition.
--
-- 'deviceDefinitionId', 'updateDeviceDefinition_deviceDefinitionId' - The ID of the device definition.
newUpdateDeviceDefinition ::
  -- | 'deviceDefinitionId'
  Prelude.Text ->
  UpdateDeviceDefinition
newUpdateDeviceDefinition :: Text -> UpdateDeviceDefinition
newUpdateDeviceDefinition Text
pDeviceDefinitionId_ =
  UpdateDeviceDefinition'
    { $sel:name:UpdateDeviceDefinition' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceDefinitionId:UpdateDeviceDefinition' :: Text
deviceDefinitionId = Text
pDeviceDefinitionId_
    }

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

-- | The ID of the device definition.
updateDeviceDefinition_deviceDefinitionId :: Lens.Lens' UpdateDeviceDefinition Prelude.Text
updateDeviceDefinition_deviceDefinitionId :: Lens' UpdateDeviceDefinition Text
updateDeviceDefinition_deviceDefinitionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDeviceDefinition' {Text
deviceDefinitionId :: Text
$sel:deviceDefinitionId:UpdateDeviceDefinition' :: UpdateDeviceDefinition -> Text
deviceDefinitionId} -> Text
deviceDefinitionId) (\s :: UpdateDeviceDefinition
s@UpdateDeviceDefinition' {} Text
a -> UpdateDeviceDefinition
s {$sel:deviceDefinitionId:UpdateDeviceDefinition' :: Text
deviceDefinitionId = Text
a} :: UpdateDeviceDefinition)

instance Core.AWSRequest UpdateDeviceDefinition where
  type
    AWSResponse UpdateDeviceDefinition =
      UpdateDeviceDefinitionResponse
  request :: (Service -> Service)
-> UpdateDeviceDefinition -> Request UpdateDeviceDefinition
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateDeviceDefinition
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateDeviceDefinition)))
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 -> UpdateDeviceDefinitionResponse
UpdateDeviceDefinitionResponse'
            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 UpdateDeviceDefinition where
  hashWithSalt :: Int -> UpdateDeviceDefinition -> Int
hashWithSalt Int
_salt UpdateDeviceDefinition' {Maybe Text
Text
deviceDefinitionId :: Text
name :: Maybe Text
$sel:deviceDefinitionId:UpdateDeviceDefinition' :: UpdateDeviceDefinition -> Text
$sel:name:UpdateDeviceDefinition' :: UpdateDeviceDefinition -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deviceDefinitionId

instance Prelude.NFData UpdateDeviceDefinition where
  rnf :: UpdateDeviceDefinition -> ()
rnf UpdateDeviceDefinition' {Maybe Text
Text
deviceDefinitionId :: Text
name :: Maybe Text
$sel:deviceDefinitionId:UpdateDeviceDefinition' :: UpdateDeviceDefinition -> Text
$sel:name:UpdateDeviceDefinition' :: UpdateDeviceDefinition -> Maybe Text
..} =
    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 Text
deviceDefinitionId

instance Data.ToHeaders UpdateDeviceDefinition where
  toHeaders :: UpdateDeviceDefinition -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateDeviceDefinition where
  toJSON :: UpdateDeviceDefinition -> Value
toJSON UpdateDeviceDefinition' {Maybe Text
Text
deviceDefinitionId :: Text
name :: Maybe Text
$sel:deviceDefinitionId:UpdateDeviceDefinition' :: UpdateDeviceDefinition -> Text
$sel:name:UpdateDeviceDefinition' :: UpdateDeviceDefinition -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(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]
      )

instance Data.ToPath UpdateDeviceDefinition where
  toPath :: UpdateDeviceDefinition -> ByteString
toPath UpdateDeviceDefinition' {Maybe Text
Text
deviceDefinitionId :: Text
name :: Maybe Text
$sel:deviceDefinitionId:UpdateDeviceDefinition' :: UpdateDeviceDefinition -> Text
$sel:name:UpdateDeviceDefinition' :: UpdateDeviceDefinition -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/greengrass/definition/devices/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
deviceDefinitionId
      ]

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

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

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

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

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