{-# 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.Lightsail.SendContactMethodVerification
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Sends a verification request to an email contact method to ensure it\'s
-- owned by the requester. SMS contact methods don\'t need to be verified.
--
-- A contact method is used to send you notifications about your Amazon
-- Lightsail resources. You can add one email address and one mobile phone
-- number contact method in each Amazon Web Services Region. However, SMS
-- text messaging is not supported in some Amazon Web Services Regions, and
-- SMS text messages cannot be sent to some countries\/regions. For more
-- information, see
-- <https://lightsail.aws.amazon.com/ls/docs/en_us/articles/amazon-lightsail-notifications Notifications in Amazon Lightsail>.
--
-- A verification request is sent to the contact method when you initially
-- create it. Use this action to send another verification request if a
-- previous verification request was deleted, or has expired.
--
-- Notifications are not sent to an email contact method until after it is
-- verified, and confirmed as valid.
module Amazonka.Lightsail.SendContactMethodVerification
  ( -- * Creating a Request
    SendContactMethodVerification (..),
    newSendContactMethodVerification,

    -- * Request Lenses
    sendContactMethodVerification_protocol,

    -- * Destructuring the Response
    SendContactMethodVerificationResponse (..),
    newSendContactMethodVerificationResponse,

    -- * Response Lenses
    sendContactMethodVerificationResponse_operations,
    sendContactMethodVerificationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newSendContactMethodVerification' smart constructor.
data SendContactMethodVerification = SendContactMethodVerification'
  { -- | The protocol to verify, such as @Email@ or @SMS@ (text messaging).
    SendContactMethodVerification -> ContactMethodVerificationProtocol
protocol :: ContactMethodVerificationProtocol
  }
  deriving (SendContactMethodVerification
-> SendContactMethodVerification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendContactMethodVerification
-> SendContactMethodVerification -> Bool
$c/= :: SendContactMethodVerification
-> SendContactMethodVerification -> Bool
== :: SendContactMethodVerification
-> SendContactMethodVerification -> Bool
$c== :: SendContactMethodVerification
-> SendContactMethodVerification -> Bool
Prelude.Eq, ReadPrec [SendContactMethodVerification]
ReadPrec SendContactMethodVerification
Int -> ReadS SendContactMethodVerification
ReadS [SendContactMethodVerification]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SendContactMethodVerification]
$creadListPrec :: ReadPrec [SendContactMethodVerification]
readPrec :: ReadPrec SendContactMethodVerification
$creadPrec :: ReadPrec SendContactMethodVerification
readList :: ReadS [SendContactMethodVerification]
$creadList :: ReadS [SendContactMethodVerification]
readsPrec :: Int -> ReadS SendContactMethodVerification
$creadsPrec :: Int -> ReadS SendContactMethodVerification
Prelude.Read, Int -> SendContactMethodVerification -> ShowS
[SendContactMethodVerification] -> ShowS
SendContactMethodVerification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendContactMethodVerification] -> ShowS
$cshowList :: [SendContactMethodVerification] -> ShowS
show :: SendContactMethodVerification -> String
$cshow :: SendContactMethodVerification -> String
showsPrec :: Int -> SendContactMethodVerification -> ShowS
$cshowsPrec :: Int -> SendContactMethodVerification -> ShowS
Prelude.Show, forall x.
Rep SendContactMethodVerification x
-> SendContactMethodVerification
forall x.
SendContactMethodVerification
-> Rep SendContactMethodVerification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SendContactMethodVerification x
-> SendContactMethodVerification
$cfrom :: forall x.
SendContactMethodVerification
-> Rep SendContactMethodVerification x
Prelude.Generic)

-- |
-- Create a value of 'SendContactMethodVerification' 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:
--
-- 'protocol', 'sendContactMethodVerification_protocol' - The protocol to verify, such as @Email@ or @SMS@ (text messaging).
newSendContactMethodVerification ::
  -- | 'protocol'
  ContactMethodVerificationProtocol ->
  SendContactMethodVerification
newSendContactMethodVerification :: ContactMethodVerificationProtocol -> SendContactMethodVerification
newSendContactMethodVerification ContactMethodVerificationProtocol
pProtocol_ =
  SendContactMethodVerification'
    { $sel:protocol:SendContactMethodVerification' :: ContactMethodVerificationProtocol
protocol =
        ContactMethodVerificationProtocol
pProtocol_
    }

-- | The protocol to verify, such as @Email@ or @SMS@ (text messaging).
sendContactMethodVerification_protocol :: Lens.Lens' SendContactMethodVerification ContactMethodVerificationProtocol
sendContactMethodVerification_protocol :: Lens'
  SendContactMethodVerification ContactMethodVerificationProtocol
sendContactMethodVerification_protocol = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendContactMethodVerification' {ContactMethodVerificationProtocol
protocol :: ContactMethodVerificationProtocol
$sel:protocol:SendContactMethodVerification' :: SendContactMethodVerification -> ContactMethodVerificationProtocol
protocol} -> ContactMethodVerificationProtocol
protocol) (\s :: SendContactMethodVerification
s@SendContactMethodVerification' {} ContactMethodVerificationProtocol
a -> SendContactMethodVerification
s {$sel:protocol:SendContactMethodVerification' :: ContactMethodVerificationProtocol
protocol = ContactMethodVerificationProtocol
a} :: SendContactMethodVerification)

instance
  Core.AWSRequest
    SendContactMethodVerification
  where
  type
    AWSResponse SendContactMethodVerification =
      SendContactMethodVerificationResponse
  request :: (Service -> Service)
-> SendContactMethodVerification
-> Request SendContactMethodVerification
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 SendContactMethodVerification
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SendContactMethodVerification)))
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 [Operation] -> Int -> SendContactMethodVerificationResponse
SendContactMethodVerificationResponse'
            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
"operations" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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
    SendContactMethodVerification
  where
  hashWithSalt :: Int -> SendContactMethodVerification -> Int
hashWithSalt Int
_salt SendContactMethodVerification' {ContactMethodVerificationProtocol
protocol :: ContactMethodVerificationProtocol
$sel:protocol:SendContactMethodVerification' :: SendContactMethodVerification -> ContactMethodVerificationProtocol
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ContactMethodVerificationProtocol
protocol

instance Prelude.NFData SendContactMethodVerification where
  rnf :: SendContactMethodVerification -> ()
rnf SendContactMethodVerification' {ContactMethodVerificationProtocol
protocol :: ContactMethodVerificationProtocol
$sel:protocol:SendContactMethodVerification' :: SendContactMethodVerification -> ContactMethodVerificationProtocol
..} =
    forall a. NFData a => a -> ()
Prelude.rnf ContactMethodVerificationProtocol
protocol

instance Data.ToHeaders SendContactMethodVerification where
  toHeaders :: SendContactMethodVerification -> 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
"Lightsail_20161128.SendContactMethodVerification" ::
                          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 SendContactMethodVerification where
  toJSON :: SendContactMethodVerification -> Value
toJSON SendContactMethodVerification' {ContactMethodVerificationProtocol
protocol :: ContactMethodVerificationProtocol
$sel:protocol:SendContactMethodVerification' :: SendContactMethodVerification -> ContactMethodVerificationProtocol
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"protocol" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ContactMethodVerificationProtocol
protocol)]
      )

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

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

-- | /See:/ 'newSendContactMethodVerificationResponse' smart constructor.
data SendContactMethodVerificationResponse = SendContactMethodVerificationResponse'
  { -- | An array of objects that describe the result of the action, such as the
    -- status of the request, the timestamp of the request, and the resources
    -- affected by the request.
    SendContactMethodVerificationResponse -> Maybe [Operation]
operations :: Prelude.Maybe [Operation],
    -- | The response's http status code.
    SendContactMethodVerificationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SendContactMethodVerificationResponse
-> SendContactMethodVerificationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendContactMethodVerificationResponse
-> SendContactMethodVerificationResponse -> Bool
$c/= :: SendContactMethodVerificationResponse
-> SendContactMethodVerificationResponse -> Bool
== :: SendContactMethodVerificationResponse
-> SendContactMethodVerificationResponse -> Bool
$c== :: SendContactMethodVerificationResponse
-> SendContactMethodVerificationResponse -> Bool
Prelude.Eq, ReadPrec [SendContactMethodVerificationResponse]
ReadPrec SendContactMethodVerificationResponse
Int -> ReadS SendContactMethodVerificationResponse
ReadS [SendContactMethodVerificationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SendContactMethodVerificationResponse]
$creadListPrec :: ReadPrec [SendContactMethodVerificationResponse]
readPrec :: ReadPrec SendContactMethodVerificationResponse
$creadPrec :: ReadPrec SendContactMethodVerificationResponse
readList :: ReadS [SendContactMethodVerificationResponse]
$creadList :: ReadS [SendContactMethodVerificationResponse]
readsPrec :: Int -> ReadS SendContactMethodVerificationResponse
$creadsPrec :: Int -> ReadS SendContactMethodVerificationResponse
Prelude.Read, Int -> SendContactMethodVerificationResponse -> ShowS
[SendContactMethodVerificationResponse] -> ShowS
SendContactMethodVerificationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendContactMethodVerificationResponse] -> ShowS
$cshowList :: [SendContactMethodVerificationResponse] -> ShowS
show :: SendContactMethodVerificationResponse -> String
$cshow :: SendContactMethodVerificationResponse -> String
showsPrec :: Int -> SendContactMethodVerificationResponse -> ShowS
$cshowsPrec :: Int -> SendContactMethodVerificationResponse -> ShowS
Prelude.Show, forall x.
Rep SendContactMethodVerificationResponse x
-> SendContactMethodVerificationResponse
forall x.
SendContactMethodVerificationResponse
-> Rep SendContactMethodVerificationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SendContactMethodVerificationResponse x
-> SendContactMethodVerificationResponse
$cfrom :: forall x.
SendContactMethodVerificationResponse
-> Rep SendContactMethodVerificationResponse x
Prelude.Generic)

-- |
-- Create a value of 'SendContactMethodVerificationResponse' 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:
--
-- 'operations', 'sendContactMethodVerificationResponse_operations' - An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
--
-- 'httpStatus', 'sendContactMethodVerificationResponse_httpStatus' - The response's http status code.
newSendContactMethodVerificationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SendContactMethodVerificationResponse
newSendContactMethodVerificationResponse :: Int -> SendContactMethodVerificationResponse
newSendContactMethodVerificationResponse Int
pHttpStatus_ =
  SendContactMethodVerificationResponse'
    { $sel:operations:SendContactMethodVerificationResponse' :: Maybe [Operation]
operations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SendContactMethodVerificationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
sendContactMethodVerificationResponse_operations :: Lens.Lens' SendContactMethodVerificationResponse (Prelude.Maybe [Operation])
sendContactMethodVerificationResponse_operations :: Lens' SendContactMethodVerificationResponse (Maybe [Operation])
sendContactMethodVerificationResponse_operations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SendContactMethodVerificationResponse' {Maybe [Operation]
operations :: Maybe [Operation]
$sel:operations:SendContactMethodVerificationResponse' :: SendContactMethodVerificationResponse -> Maybe [Operation]
operations} -> Maybe [Operation]
operations) (\s :: SendContactMethodVerificationResponse
s@SendContactMethodVerificationResponse' {} Maybe [Operation]
a -> SendContactMethodVerificationResponse
s {$sel:operations:SendContactMethodVerificationResponse' :: Maybe [Operation]
operations = Maybe [Operation]
a} :: SendContactMethodVerificationResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance
  Prelude.NFData
    SendContactMethodVerificationResponse
  where
  rnf :: SendContactMethodVerificationResponse -> ()
rnf SendContactMethodVerificationResponse' {Int
Maybe [Operation]
httpStatus :: Int
operations :: Maybe [Operation]
$sel:httpStatus:SendContactMethodVerificationResponse' :: SendContactMethodVerificationResponse -> Int
$sel:operations:SendContactMethodVerificationResponse' :: SendContactMethodVerificationResponse -> Maybe [Operation]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Operation]
operations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus