{-# 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.CloudDirectory.DetachTypedLink
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Detaches a typed link from a specified source and target object. For
-- more information, see
-- <https://docs.aws.amazon.com/clouddirectory/latest/developerguide/directory_objects_links.html#directory_objects_links_typedlink Typed Links>.
module Amazonka.CloudDirectory.DetachTypedLink
  ( -- * Creating a Request
    DetachTypedLink (..),
    newDetachTypedLink,

    -- * Request Lenses
    detachTypedLink_directoryArn,
    detachTypedLink_typedLinkSpecifier,

    -- * Destructuring the Response
    DetachTypedLinkResponse (..),
    newDetachTypedLinkResponse,
  )
where

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

-- | /See:/ 'newDetachTypedLink' smart constructor.
data DetachTypedLink = DetachTypedLink'
  { -- | The Amazon Resource Name (ARN) of the directory where you want to detach
    -- the typed link.
    DetachTypedLink -> Text
directoryArn :: Prelude.Text,
    -- | Used to accept a typed link specifier as input.
    DetachTypedLink -> TypedLinkSpecifier
typedLinkSpecifier :: TypedLinkSpecifier
  }
  deriving (DetachTypedLink -> DetachTypedLink -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachTypedLink -> DetachTypedLink -> Bool
$c/= :: DetachTypedLink -> DetachTypedLink -> Bool
== :: DetachTypedLink -> DetachTypedLink -> Bool
$c== :: DetachTypedLink -> DetachTypedLink -> Bool
Prelude.Eq, ReadPrec [DetachTypedLink]
ReadPrec DetachTypedLink
Int -> ReadS DetachTypedLink
ReadS [DetachTypedLink]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachTypedLink]
$creadListPrec :: ReadPrec [DetachTypedLink]
readPrec :: ReadPrec DetachTypedLink
$creadPrec :: ReadPrec DetachTypedLink
readList :: ReadS [DetachTypedLink]
$creadList :: ReadS [DetachTypedLink]
readsPrec :: Int -> ReadS DetachTypedLink
$creadsPrec :: Int -> ReadS DetachTypedLink
Prelude.Read, Int -> DetachTypedLink -> ShowS
[DetachTypedLink] -> ShowS
DetachTypedLink -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachTypedLink] -> ShowS
$cshowList :: [DetachTypedLink] -> ShowS
show :: DetachTypedLink -> String
$cshow :: DetachTypedLink -> String
showsPrec :: Int -> DetachTypedLink -> ShowS
$cshowsPrec :: Int -> DetachTypedLink -> ShowS
Prelude.Show, forall x. Rep DetachTypedLink x -> DetachTypedLink
forall x. DetachTypedLink -> Rep DetachTypedLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetachTypedLink x -> DetachTypedLink
$cfrom :: forall x. DetachTypedLink -> Rep DetachTypedLink x
Prelude.Generic)

-- |
-- Create a value of 'DetachTypedLink' 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:
--
-- 'directoryArn', 'detachTypedLink_directoryArn' - The Amazon Resource Name (ARN) of the directory where you want to detach
-- the typed link.
--
-- 'typedLinkSpecifier', 'detachTypedLink_typedLinkSpecifier' - Used to accept a typed link specifier as input.
newDetachTypedLink ::
  -- | 'directoryArn'
  Prelude.Text ->
  -- | 'typedLinkSpecifier'
  TypedLinkSpecifier ->
  DetachTypedLink
newDetachTypedLink :: Text -> TypedLinkSpecifier -> DetachTypedLink
newDetachTypedLink
  Text
pDirectoryArn_
  TypedLinkSpecifier
pTypedLinkSpecifier_ =
    DetachTypedLink'
      { $sel:directoryArn:DetachTypedLink' :: Text
directoryArn = Text
pDirectoryArn_,
        $sel:typedLinkSpecifier:DetachTypedLink' :: TypedLinkSpecifier
typedLinkSpecifier = TypedLinkSpecifier
pTypedLinkSpecifier_
      }

-- | The Amazon Resource Name (ARN) of the directory where you want to detach
-- the typed link.
detachTypedLink_directoryArn :: Lens.Lens' DetachTypedLink Prelude.Text
detachTypedLink_directoryArn :: Lens' DetachTypedLink Text
detachTypedLink_directoryArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachTypedLink' {Text
directoryArn :: Text
$sel:directoryArn:DetachTypedLink' :: DetachTypedLink -> Text
directoryArn} -> Text
directoryArn) (\s :: DetachTypedLink
s@DetachTypedLink' {} Text
a -> DetachTypedLink
s {$sel:directoryArn:DetachTypedLink' :: Text
directoryArn = Text
a} :: DetachTypedLink)

-- | Used to accept a typed link specifier as input.
detachTypedLink_typedLinkSpecifier :: Lens.Lens' DetachTypedLink TypedLinkSpecifier
detachTypedLink_typedLinkSpecifier :: Lens' DetachTypedLink TypedLinkSpecifier
detachTypedLink_typedLinkSpecifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachTypedLink' {TypedLinkSpecifier
typedLinkSpecifier :: TypedLinkSpecifier
$sel:typedLinkSpecifier:DetachTypedLink' :: DetachTypedLink -> TypedLinkSpecifier
typedLinkSpecifier} -> TypedLinkSpecifier
typedLinkSpecifier) (\s :: DetachTypedLink
s@DetachTypedLink' {} TypedLinkSpecifier
a -> DetachTypedLink
s {$sel:typedLinkSpecifier:DetachTypedLink' :: TypedLinkSpecifier
typedLinkSpecifier = TypedLinkSpecifier
a} :: DetachTypedLink)

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

instance Prelude.Hashable DetachTypedLink where
  hashWithSalt :: Int -> DetachTypedLink -> Int
hashWithSalt Int
_salt DetachTypedLink' {Text
TypedLinkSpecifier
typedLinkSpecifier :: TypedLinkSpecifier
directoryArn :: Text
$sel:typedLinkSpecifier:DetachTypedLink' :: DetachTypedLink -> TypedLinkSpecifier
$sel:directoryArn:DetachTypedLink' :: DetachTypedLink -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TypedLinkSpecifier
typedLinkSpecifier

instance Prelude.NFData DetachTypedLink where
  rnf :: DetachTypedLink -> ()
rnf DetachTypedLink' {Text
TypedLinkSpecifier
typedLinkSpecifier :: TypedLinkSpecifier
directoryArn :: Text
$sel:typedLinkSpecifier:DetachTypedLink' :: DetachTypedLink -> TypedLinkSpecifier
$sel:directoryArn:DetachTypedLink' :: DetachTypedLink -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
directoryArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TypedLinkSpecifier
typedLinkSpecifier

instance Data.ToHeaders DetachTypedLink where
  toHeaders :: DetachTypedLink -> [Header]
toHeaders DetachTypedLink' {Text
TypedLinkSpecifier
typedLinkSpecifier :: TypedLinkSpecifier
directoryArn :: Text
$sel:typedLinkSpecifier:DetachTypedLink' :: DetachTypedLink -> TypedLinkSpecifier
$sel:directoryArn:DetachTypedLink' :: DetachTypedLink -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [HeaderName
"x-amz-data-partition" forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# Text
directoryArn]

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

instance Data.ToPath DetachTypedLink where
  toPath :: DetachTypedLink -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/amazonclouddirectory/2017-01-11/typedlink/detach"

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

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

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

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