{-# 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.Organizations.DeclineHandshake
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Declines a handshake request. This sets the handshake state to
-- @DECLINED@ and effectively deactivates the request.
--
-- This operation can be called only from the account that received the
-- handshake. The originator of the handshake can use CancelHandshake
-- instead. The originator can\'t reactivate a declined request, but can
-- reinitiate the process with a new handshake request.
--
-- After you decline a handshake, it continues to appear in the results of
-- relevant APIs for only 30 days. After that, it\'s deleted.
module Amazonka.Organizations.DeclineHandshake
  ( -- * Creating a Request
    DeclineHandshake (..),
    newDeclineHandshake,

    -- * Request Lenses
    declineHandshake_handshakeId,

    -- * Destructuring the Response
    DeclineHandshakeResponse (..),
    newDeclineHandshakeResponse,

    -- * Response Lenses
    declineHandshakeResponse_handshake,
    declineHandshakeResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeclineHandshake' smart constructor.
data DeclineHandshake = DeclineHandshake'
  { -- | The unique identifier (ID) of the handshake that you want to decline.
    -- You can get the ID from the ListHandshakesForAccount operation.
    --
    -- The <http://wikipedia.org/wiki/regex regex pattern> for handshake ID
    -- string requires \"h-\" followed by from 8 to 32 lowercase letters or
    -- digits.
    DeclineHandshake -> Text
handshakeId :: Prelude.Text
  }
  deriving (DeclineHandshake -> DeclineHandshake -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeclineHandshake -> DeclineHandshake -> Bool
$c/= :: DeclineHandshake -> DeclineHandshake -> Bool
== :: DeclineHandshake -> DeclineHandshake -> Bool
$c== :: DeclineHandshake -> DeclineHandshake -> Bool
Prelude.Eq, ReadPrec [DeclineHandshake]
ReadPrec DeclineHandshake
Int -> ReadS DeclineHandshake
ReadS [DeclineHandshake]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeclineHandshake]
$creadListPrec :: ReadPrec [DeclineHandshake]
readPrec :: ReadPrec DeclineHandshake
$creadPrec :: ReadPrec DeclineHandshake
readList :: ReadS [DeclineHandshake]
$creadList :: ReadS [DeclineHandshake]
readsPrec :: Int -> ReadS DeclineHandshake
$creadsPrec :: Int -> ReadS DeclineHandshake
Prelude.Read, Int -> DeclineHandshake -> ShowS
[DeclineHandshake] -> ShowS
DeclineHandshake -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeclineHandshake] -> ShowS
$cshowList :: [DeclineHandshake] -> ShowS
show :: DeclineHandshake -> String
$cshow :: DeclineHandshake -> String
showsPrec :: Int -> DeclineHandshake -> ShowS
$cshowsPrec :: Int -> DeclineHandshake -> ShowS
Prelude.Show, forall x. Rep DeclineHandshake x -> DeclineHandshake
forall x. DeclineHandshake -> Rep DeclineHandshake x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeclineHandshake x -> DeclineHandshake
$cfrom :: forall x. DeclineHandshake -> Rep DeclineHandshake x
Prelude.Generic)

-- |
-- Create a value of 'DeclineHandshake' 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:
--
-- 'handshakeId', 'declineHandshake_handshakeId' - The unique identifier (ID) of the handshake that you want to decline.
-- You can get the ID from the ListHandshakesForAccount operation.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> for handshake ID
-- string requires \"h-\" followed by from 8 to 32 lowercase letters or
-- digits.
newDeclineHandshake ::
  -- | 'handshakeId'
  Prelude.Text ->
  DeclineHandshake
newDeclineHandshake :: Text -> DeclineHandshake
newDeclineHandshake Text
pHandshakeId_ =
  DeclineHandshake' {$sel:handshakeId:DeclineHandshake' :: Text
handshakeId = Text
pHandshakeId_}

-- | The unique identifier (ID) of the handshake that you want to decline.
-- You can get the ID from the ListHandshakesForAccount operation.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> for handshake ID
-- string requires \"h-\" followed by from 8 to 32 lowercase letters or
-- digits.
declineHandshake_handshakeId :: Lens.Lens' DeclineHandshake Prelude.Text
declineHandshake_handshakeId :: Lens' DeclineHandshake Text
declineHandshake_handshakeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeclineHandshake' {Text
handshakeId :: Text
$sel:handshakeId:DeclineHandshake' :: DeclineHandshake -> Text
handshakeId} -> Text
handshakeId) (\s :: DeclineHandshake
s@DeclineHandshake' {} Text
a -> DeclineHandshake
s {$sel:handshakeId:DeclineHandshake' :: Text
handshakeId = Text
a} :: DeclineHandshake)

instance Core.AWSRequest DeclineHandshake where
  type
    AWSResponse DeclineHandshake =
      DeclineHandshakeResponse
  request :: (Service -> Service)
-> DeclineHandshake -> Request DeclineHandshake
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 DeclineHandshake
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeclineHandshake)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Handshake -> Int -> DeclineHandshakeResponse
DeclineHandshakeResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Handshake")
            forall (f :: * -> *) a b. Applicative f => 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 DeclineHandshake where
  hashWithSalt :: Int -> DeclineHandshake -> Int
hashWithSalt Int
_salt DeclineHandshake' {Text
handshakeId :: Text
$sel:handshakeId:DeclineHandshake' :: DeclineHandshake -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
handshakeId

instance Prelude.NFData DeclineHandshake where
  rnf :: DeclineHandshake -> ()
rnf DeclineHandshake' {Text
handshakeId :: Text
$sel:handshakeId:DeclineHandshake' :: DeclineHandshake -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
handshakeId

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

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

instance Data.ToPath DeclineHandshake where
  toPath :: DeclineHandshake -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDeclineHandshakeResponse' smart constructor.
data DeclineHandshakeResponse = DeclineHandshakeResponse'
  { -- | A structure that contains details about the declined handshake. The
    -- state is updated to show the value @DECLINED@.
    DeclineHandshakeResponse -> Maybe Handshake
handshake :: Prelude.Maybe Handshake,
    -- | The response's http status code.
    DeclineHandshakeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeclineHandshakeResponse -> DeclineHandshakeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeclineHandshakeResponse -> DeclineHandshakeResponse -> Bool
$c/= :: DeclineHandshakeResponse -> DeclineHandshakeResponse -> Bool
== :: DeclineHandshakeResponse -> DeclineHandshakeResponse -> Bool
$c== :: DeclineHandshakeResponse -> DeclineHandshakeResponse -> Bool
Prelude.Eq, Int -> DeclineHandshakeResponse -> ShowS
[DeclineHandshakeResponse] -> ShowS
DeclineHandshakeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeclineHandshakeResponse] -> ShowS
$cshowList :: [DeclineHandshakeResponse] -> ShowS
show :: DeclineHandshakeResponse -> String
$cshow :: DeclineHandshakeResponse -> String
showsPrec :: Int -> DeclineHandshakeResponse -> ShowS
$cshowsPrec :: Int -> DeclineHandshakeResponse -> ShowS
Prelude.Show, forall x.
Rep DeclineHandshakeResponse x -> DeclineHandshakeResponse
forall x.
DeclineHandshakeResponse -> Rep DeclineHandshakeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeclineHandshakeResponse x -> DeclineHandshakeResponse
$cfrom :: forall x.
DeclineHandshakeResponse -> Rep DeclineHandshakeResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeclineHandshakeResponse' 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:
--
-- 'handshake', 'declineHandshakeResponse_handshake' - A structure that contains details about the declined handshake. The
-- state is updated to show the value @DECLINED@.
--
-- 'httpStatus', 'declineHandshakeResponse_httpStatus' - The response's http status code.
newDeclineHandshakeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeclineHandshakeResponse
newDeclineHandshakeResponse :: Int -> DeclineHandshakeResponse
newDeclineHandshakeResponse Int
pHttpStatus_ =
  DeclineHandshakeResponse'
    { $sel:handshake:DeclineHandshakeResponse' :: Maybe Handshake
handshake =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeclineHandshakeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A structure that contains details about the declined handshake. The
-- state is updated to show the value @DECLINED@.
declineHandshakeResponse_handshake :: Lens.Lens' DeclineHandshakeResponse (Prelude.Maybe Handshake)
declineHandshakeResponse_handshake :: Lens' DeclineHandshakeResponse (Maybe Handshake)
declineHandshakeResponse_handshake = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeclineHandshakeResponse' {Maybe Handshake
handshake :: Maybe Handshake
$sel:handshake:DeclineHandshakeResponse' :: DeclineHandshakeResponse -> Maybe Handshake
handshake} -> Maybe Handshake
handshake) (\s :: DeclineHandshakeResponse
s@DeclineHandshakeResponse' {} Maybe Handshake
a -> DeclineHandshakeResponse
s {$sel:handshake:DeclineHandshakeResponse' :: Maybe Handshake
handshake = Maybe Handshake
a} :: DeclineHandshakeResponse)

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

instance Prelude.NFData DeclineHandshakeResponse where
  rnf :: DeclineHandshakeResponse -> ()
rnf DeclineHandshakeResponse' {Int
Maybe Handshake
httpStatus :: Int
handshake :: Maybe Handshake
$sel:httpStatus:DeclineHandshakeResponse' :: DeclineHandshakeResponse -> Int
$sel:handshake:DeclineHandshakeResponse' :: DeclineHandshakeResponse -> Maybe Handshake
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Handshake
handshake
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus