{-# 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.AssociateWirelessDeviceWithThing
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associates a wireless device with a thing.
module Amazonka.IoTWireless.AssociateWirelessDeviceWithThing
  ( -- * Creating a Request
    AssociateWirelessDeviceWithThing (..),
    newAssociateWirelessDeviceWithThing,

    -- * Request Lenses
    associateWirelessDeviceWithThing_id,
    associateWirelessDeviceWithThing_thingArn,

    -- * Destructuring the Response
    AssociateWirelessDeviceWithThingResponse (..),
    newAssociateWirelessDeviceWithThingResponse,

    -- * Response Lenses
    associateWirelessDeviceWithThingResponse_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:/ 'newAssociateWirelessDeviceWithThing' smart constructor.
data AssociateWirelessDeviceWithThing = AssociateWirelessDeviceWithThing'
  { -- | The ID of the resource to update.
    AssociateWirelessDeviceWithThing -> Text
id :: Prelude.Text,
    -- | The ARN of the thing to associate with the wireless device.
    AssociateWirelessDeviceWithThing -> Text
thingArn :: Prelude.Text
  }
  deriving (AssociateWirelessDeviceWithThing
-> AssociateWirelessDeviceWithThing -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateWirelessDeviceWithThing
-> AssociateWirelessDeviceWithThing -> Bool
$c/= :: AssociateWirelessDeviceWithThing
-> AssociateWirelessDeviceWithThing -> Bool
== :: AssociateWirelessDeviceWithThing
-> AssociateWirelessDeviceWithThing -> Bool
$c== :: AssociateWirelessDeviceWithThing
-> AssociateWirelessDeviceWithThing -> Bool
Prelude.Eq, ReadPrec [AssociateWirelessDeviceWithThing]
ReadPrec AssociateWirelessDeviceWithThing
Int -> ReadS AssociateWirelessDeviceWithThing
ReadS [AssociateWirelessDeviceWithThing]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateWirelessDeviceWithThing]
$creadListPrec :: ReadPrec [AssociateWirelessDeviceWithThing]
readPrec :: ReadPrec AssociateWirelessDeviceWithThing
$creadPrec :: ReadPrec AssociateWirelessDeviceWithThing
readList :: ReadS [AssociateWirelessDeviceWithThing]
$creadList :: ReadS [AssociateWirelessDeviceWithThing]
readsPrec :: Int -> ReadS AssociateWirelessDeviceWithThing
$creadsPrec :: Int -> ReadS AssociateWirelessDeviceWithThing
Prelude.Read, Int -> AssociateWirelessDeviceWithThing -> ShowS
[AssociateWirelessDeviceWithThing] -> ShowS
AssociateWirelessDeviceWithThing -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateWirelessDeviceWithThing] -> ShowS
$cshowList :: [AssociateWirelessDeviceWithThing] -> ShowS
show :: AssociateWirelessDeviceWithThing -> String
$cshow :: AssociateWirelessDeviceWithThing -> String
showsPrec :: Int -> AssociateWirelessDeviceWithThing -> ShowS
$cshowsPrec :: Int -> AssociateWirelessDeviceWithThing -> ShowS
Prelude.Show, forall x.
Rep AssociateWirelessDeviceWithThing x
-> AssociateWirelessDeviceWithThing
forall x.
AssociateWirelessDeviceWithThing
-> Rep AssociateWirelessDeviceWithThing x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateWirelessDeviceWithThing x
-> AssociateWirelessDeviceWithThing
$cfrom :: forall x.
AssociateWirelessDeviceWithThing
-> Rep AssociateWirelessDeviceWithThing x
Prelude.Generic)

-- |
-- Create a value of 'AssociateWirelessDeviceWithThing' 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:
--
-- 'id', 'associateWirelessDeviceWithThing_id' - The ID of the resource to update.
--
-- 'thingArn', 'associateWirelessDeviceWithThing_thingArn' - The ARN of the thing to associate with the wireless device.
newAssociateWirelessDeviceWithThing ::
  -- | 'id'
  Prelude.Text ->
  -- | 'thingArn'
  Prelude.Text ->
  AssociateWirelessDeviceWithThing
newAssociateWirelessDeviceWithThing :: Text -> Text -> AssociateWirelessDeviceWithThing
newAssociateWirelessDeviceWithThing Text
pId_ Text
pThingArn_ =
  AssociateWirelessDeviceWithThing'
    { $sel:id:AssociateWirelessDeviceWithThing' :: Text
id = Text
pId_,
      $sel:thingArn:AssociateWirelessDeviceWithThing' :: Text
thingArn = Text
pThingArn_
    }

-- | The ID of the resource to update.
associateWirelessDeviceWithThing_id :: Lens.Lens' AssociateWirelessDeviceWithThing Prelude.Text
associateWirelessDeviceWithThing_id :: Lens' AssociateWirelessDeviceWithThing Text
associateWirelessDeviceWithThing_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateWirelessDeviceWithThing' {Text
id :: Text
$sel:id:AssociateWirelessDeviceWithThing' :: AssociateWirelessDeviceWithThing -> Text
id} -> Text
id) (\s :: AssociateWirelessDeviceWithThing
s@AssociateWirelessDeviceWithThing' {} Text
a -> AssociateWirelessDeviceWithThing
s {$sel:id:AssociateWirelessDeviceWithThing' :: Text
id = Text
a} :: AssociateWirelessDeviceWithThing)

-- | The ARN of the thing to associate with the wireless device.
associateWirelessDeviceWithThing_thingArn :: Lens.Lens' AssociateWirelessDeviceWithThing Prelude.Text
associateWirelessDeviceWithThing_thingArn :: Lens' AssociateWirelessDeviceWithThing Text
associateWirelessDeviceWithThing_thingArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateWirelessDeviceWithThing' {Text
thingArn :: Text
$sel:thingArn:AssociateWirelessDeviceWithThing' :: AssociateWirelessDeviceWithThing -> Text
thingArn} -> Text
thingArn) (\s :: AssociateWirelessDeviceWithThing
s@AssociateWirelessDeviceWithThing' {} Text
a -> AssociateWirelessDeviceWithThing
s {$sel:thingArn:AssociateWirelessDeviceWithThing' :: Text
thingArn = Text
a} :: AssociateWirelessDeviceWithThing)

instance
  Core.AWSRequest
    AssociateWirelessDeviceWithThing
  where
  type
    AWSResponse AssociateWirelessDeviceWithThing =
      AssociateWirelessDeviceWithThingResponse
  request :: (Service -> Service)
-> AssociateWirelessDeviceWithThing
-> Request AssociateWirelessDeviceWithThing
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 AssociateWirelessDeviceWithThing
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse AssociateWirelessDeviceWithThing)))
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 -> AssociateWirelessDeviceWithThingResponse
AssociateWirelessDeviceWithThingResponse'
            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
    AssociateWirelessDeviceWithThing
  where
  hashWithSalt :: Int -> AssociateWirelessDeviceWithThing -> Int
hashWithSalt
    Int
_salt
    AssociateWirelessDeviceWithThing' {Text
thingArn :: Text
id :: Text
$sel:thingArn:AssociateWirelessDeviceWithThing' :: AssociateWirelessDeviceWithThing -> Text
$sel:id:AssociateWirelessDeviceWithThing' :: AssociateWirelessDeviceWithThing -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingArn

instance
  Prelude.NFData
    AssociateWirelessDeviceWithThing
  where
  rnf :: AssociateWirelessDeviceWithThing -> ()
rnf AssociateWirelessDeviceWithThing' {Text
thingArn :: Text
id :: Text
$sel:thingArn:AssociateWirelessDeviceWithThing' :: AssociateWirelessDeviceWithThing -> Text
$sel:id:AssociateWirelessDeviceWithThing' :: AssociateWirelessDeviceWithThing -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
id seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
thingArn

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

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

instance Data.ToPath AssociateWirelessDeviceWithThing where
  toPath :: AssociateWirelessDeviceWithThing -> ByteString
toPath AssociateWirelessDeviceWithThing' {Text
thingArn :: Text
id :: Text
$sel:thingArn:AssociateWirelessDeviceWithThing' :: AssociateWirelessDeviceWithThing -> Text
$sel:id:AssociateWirelessDeviceWithThing' :: AssociateWirelessDeviceWithThing -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/wireless-devices/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id, ByteString
"/thing"]

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

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

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

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

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