{-# 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.IoTSiteWise.AssociateAssets
-- 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 child asset with the given parent asset through a hierarchy
-- defined in the parent asset\'s model. For more information, see
-- <https://docs.aws.amazon.com/iot-sitewise/latest/userguide/add-associated-assets.html Associating assets>
-- in the /IoT SiteWise User Guide/.
module Amazonka.IoTSiteWise.AssociateAssets
  ( -- * Creating a Request
    AssociateAssets (..),
    newAssociateAssets,

    -- * Request Lenses
    associateAssets_clientToken,
    associateAssets_assetId,
    associateAssets_hierarchyId,
    associateAssets_childAssetId,

    -- * Destructuring the Response
    AssociateAssetsResponse (..),
    newAssociateAssetsResponse,
  )
where

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

-- | /See:/ 'newAssociateAssets' smart constructor.
data AssociateAssets = AssociateAssets'
  { -- | A unique case-sensitive identifier that you can provide to ensure the
    -- idempotency of the request. Don\'t reuse this client token if a new
    -- idempotent request is required.
    AssociateAssets -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the parent asset.
    AssociateAssets -> Text
assetId :: Prelude.Text,
    -- | The ID of a hierarchy in the parent asset\'s model. Hierarchies allow
    -- different groupings of assets to be formed that all come from the same
    -- asset model. For more information, see
    -- <https://docs.aws.amazon.com/iot-sitewise/latest/userguide/asset-hierarchies.html Asset hierarchies>
    -- in the /IoT SiteWise User Guide/.
    AssociateAssets -> Text
hierarchyId :: Prelude.Text,
    -- | The ID of the child asset to be associated.
    AssociateAssets -> Text
childAssetId :: Prelude.Text
  }
  deriving (AssociateAssets -> AssociateAssets -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateAssets -> AssociateAssets -> Bool
$c/= :: AssociateAssets -> AssociateAssets -> Bool
== :: AssociateAssets -> AssociateAssets -> Bool
$c== :: AssociateAssets -> AssociateAssets -> Bool
Prelude.Eq, ReadPrec [AssociateAssets]
ReadPrec AssociateAssets
Int -> ReadS AssociateAssets
ReadS [AssociateAssets]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateAssets]
$creadListPrec :: ReadPrec [AssociateAssets]
readPrec :: ReadPrec AssociateAssets
$creadPrec :: ReadPrec AssociateAssets
readList :: ReadS [AssociateAssets]
$creadList :: ReadS [AssociateAssets]
readsPrec :: Int -> ReadS AssociateAssets
$creadsPrec :: Int -> ReadS AssociateAssets
Prelude.Read, Int -> AssociateAssets -> ShowS
[AssociateAssets] -> ShowS
AssociateAssets -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateAssets] -> ShowS
$cshowList :: [AssociateAssets] -> ShowS
show :: AssociateAssets -> String
$cshow :: AssociateAssets -> String
showsPrec :: Int -> AssociateAssets -> ShowS
$cshowsPrec :: Int -> AssociateAssets -> ShowS
Prelude.Show, forall x. Rep AssociateAssets x -> AssociateAssets
forall x. AssociateAssets -> Rep AssociateAssets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssociateAssets x -> AssociateAssets
$cfrom :: forall x. AssociateAssets -> Rep AssociateAssets x
Prelude.Generic)

-- |
-- Create a value of 'AssociateAssets' 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:
--
-- 'clientToken', 'associateAssets_clientToken' - A unique case-sensitive identifier that you can provide to ensure the
-- idempotency of the request. Don\'t reuse this client token if a new
-- idempotent request is required.
--
-- 'assetId', 'associateAssets_assetId' - The ID of the parent asset.
--
-- 'hierarchyId', 'associateAssets_hierarchyId' - The ID of a hierarchy in the parent asset\'s model. Hierarchies allow
-- different groupings of assets to be formed that all come from the same
-- asset model. For more information, see
-- <https://docs.aws.amazon.com/iot-sitewise/latest/userguide/asset-hierarchies.html Asset hierarchies>
-- in the /IoT SiteWise User Guide/.
--
-- 'childAssetId', 'associateAssets_childAssetId' - The ID of the child asset to be associated.
newAssociateAssets ::
  -- | 'assetId'
  Prelude.Text ->
  -- | 'hierarchyId'
  Prelude.Text ->
  -- | 'childAssetId'
  Prelude.Text ->
  AssociateAssets
newAssociateAssets :: Text -> Text -> Text -> AssociateAssets
newAssociateAssets
  Text
pAssetId_
  Text
pHierarchyId_
  Text
pChildAssetId_ =
    AssociateAssets'
      { $sel:clientToken:AssociateAssets' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
        $sel:assetId:AssociateAssets' :: Text
assetId = Text
pAssetId_,
        $sel:hierarchyId:AssociateAssets' :: Text
hierarchyId = Text
pHierarchyId_,
        $sel:childAssetId:AssociateAssets' :: Text
childAssetId = Text
pChildAssetId_
      }

-- | A unique case-sensitive identifier that you can provide to ensure the
-- idempotency of the request. Don\'t reuse this client token if a new
-- idempotent request is required.
associateAssets_clientToken :: Lens.Lens' AssociateAssets (Prelude.Maybe Prelude.Text)
associateAssets_clientToken :: Lens' AssociateAssets (Maybe Text)
associateAssets_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateAssets' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:AssociateAssets' :: AssociateAssets -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: AssociateAssets
s@AssociateAssets' {} Maybe Text
a -> AssociateAssets
s {$sel:clientToken:AssociateAssets' :: Maybe Text
clientToken = Maybe Text
a} :: AssociateAssets)

-- | The ID of the parent asset.
associateAssets_assetId :: Lens.Lens' AssociateAssets Prelude.Text
associateAssets_assetId :: Lens' AssociateAssets Text
associateAssets_assetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateAssets' {Text
assetId :: Text
$sel:assetId:AssociateAssets' :: AssociateAssets -> Text
assetId} -> Text
assetId) (\s :: AssociateAssets
s@AssociateAssets' {} Text
a -> AssociateAssets
s {$sel:assetId:AssociateAssets' :: Text
assetId = Text
a} :: AssociateAssets)

-- | The ID of a hierarchy in the parent asset\'s model. Hierarchies allow
-- different groupings of assets to be formed that all come from the same
-- asset model. For more information, see
-- <https://docs.aws.amazon.com/iot-sitewise/latest/userguide/asset-hierarchies.html Asset hierarchies>
-- in the /IoT SiteWise User Guide/.
associateAssets_hierarchyId :: Lens.Lens' AssociateAssets Prelude.Text
associateAssets_hierarchyId :: Lens' AssociateAssets Text
associateAssets_hierarchyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateAssets' {Text
hierarchyId :: Text
$sel:hierarchyId:AssociateAssets' :: AssociateAssets -> Text
hierarchyId} -> Text
hierarchyId) (\s :: AssociateAssets
s@AssociateAssets' {} Text
a -> AssociateAssets
s {$sel:hierarchyId:AssociateAssets' :: Text
hierarchyId = Text
a} :: AssociateAssets)

-- | The ID of the child asset to be associated.
associateAssets_childAssetId :: Lens.Lens' AssociateAssets Prelude.Text
associateAssets_childAssetId :: Lens' AssociateAssets Text
associateAssets_childAssetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateAssets' {Text
childAssetId :: Text
$sel:childAssetId:AssociateAssets' :: AssociateAssets -> Text
childAssetId} -> Text
childAssetId) (\s :: AssociateAssets
s@AssociateAssets' {} Text
a -> AssociateAssets
s {$sel:childAssetId:AssociateAssets' :: Text
childAssetId = Text
a} :: AssociateAssets)

instance Core.AWSRequest AssociateAssets where
  type
    AWSResponse AssociateAssets =
      AssociateAssetsResponse
  request :: (Service -> Service) -> AssociateAssets -> Request AssociateAssets
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 AssociateAssets
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AssociateAssets)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull AssociateAssetsResponse
AssociateAssetsResponse'

instance Prelude.Hashable AssociateAssets where
  hashWithSalt :: Int -> AssociateAssets -> Int
hashWithSalt Int
_salt AssociateAssets' {Maybe Text
Text
childAssetId :: Text
hierarchyId :: Text
assetId :: Text
clientToken :: Maybe Text
$sel:childAssetId:AssociateAssets' :: AssociateAssets -> Text
$sel:hierarchyId:AssociateAssets' :: AssociateAssets -> Text
$sel:assetId:AssociateAssets' :: AssociateAssets -> Text
$sel:clientToken:AssociateAssets' :: AssociateAssets -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
assetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
hierarchyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
childAssetId

instance Prelude.NFData AssociateAssets where
  rnf :: AssociateAssets -> ()
rnf AssociateAssets' {Maybe Text
Text
childAssetId :: Text
hierarchyId :: Text
assetId :: Text
clientToken :: Maybe Text
$sel:childAssetId:AssociateAssets' :: AssociateAssets -> Text
$sel:hierarchyId:AssociateAssets' :: AssociateAssets -> Text
$sel:assetId:AssociateAssets' :: AssociateAssets -> Text
$sel:clientToken:AssociateAssets' :: AssociateAssets -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
assetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
hierarchyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
childAssetId

instance Data.ToHeaders AssociateAssets where
  toHeaders :: AssociateAssets -> [Header]
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 -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON AssociateAssets where
  toJSON :: AssociateAssets -> Value
toJSON AssociateAssets' {Maybe Text
Text
childAssetId :: Text
hierarchyId :: Text
assetId :: Text
clientToken :: Maybe Text
$sel:childAssetId:AssociateAssets' :: AssociateAssets -> Text
$sel:hierarchyId:AssociateAssets' :: AssociateAssets -> Text
$sel:assetId:AssociateAssets' :: AssociateAssets -> Text
$sel:clientToken:AssociateAssets' :: AssociateAssets -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"clientToken" 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
clientToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"hierarchyId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
hierarchyId),
            forall a. a -> Maybe a
Prelude.Just (Key
"childAssetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
childAssetId)
          ]
      )

instance Data.ToPath AssociateAssets where
  toPath :: AssociateAssets -> ByteString
toPath AssociateAssets' {Maybe Text
Text
childAssetId :: Text
hierarchyId :: Text
assetId :: Text
clientToken :: Maybe Text
$sel:childAssetId:AssociateAssets' :: AssociateAssets -> Text
$sel:hierarchyId:AssociateAssets' :: AssociateAssets -> Text
$sel:assetId:AssociateAssets' :: AssociateAssets -> Text
$sel:clientToken:AssociateAssets' :: AssociateAssets -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/assets/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
assetId, ByteString
"/associate"]

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

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

-- |
-- Create a value of 'AssociateAssetsResponse' 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.
newAssociateAssetsResponse ::
  AssociateAssetsResponse
newAssociateAssetsResponse :: AssociateAssetsResponse
newAssociateAssetsResponse = AssociateAssetsResponse
AssociateAssetsResponse'

instance Prelude.NFData AssociateAssetsResponse where
  rnf :: AssociateAssetsResponse -> ()
rnf AssociateAssetsResponse
_ = ()