{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.MechanicalTurk.Types.NotificationSpecification
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.MechanicalTurk.Types.NotificationSpecification where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MechanicalTurk.Types.EventType
import Amazonka.MechanicalTurk.Types.NotificationTransport
import qualified Amazonka.Prelude as Prelude

-- | The NotificationSpecification data structure describes a HIT event
-- notification for a HIT type.
--
-- /See:/ 'newNotificationSpecification' smart constructor.
data NotificationSpecification = NotificationSpecification'
  { -- | The target for notification messages. The Destination’s format is
    -- determined by the specified Transport:
    --
    -- -   When Transport is Email, the Destination is your email address.
    --
    -- -   When Transport is SQS, the Destination is your queue URL.
    --
    -- -   When Transport is SNS, the Destination is the ARN of your topic.
    NotificationSpecification -> Text
destination :: Prelude.Text,
    -- | The method Amazon Mechanical Turk uses to send the notification. Valid
    -- Values: Email | SQS | SNS.
    NotificationSpecification -> NotificationTransport
transport :: NotificationTransport,
    -- | The version of the Notification API to use. Valid value is 2006-05-05.
    NotificationSpecification -> Text
version :: Prelude.Text,
    -- | The list of events that should cause notifications to be sent. Valid
    -- Values: AssignmentAccepted | AssignmentAbandoned | AssignmentReturned |
    -- AssignmentSubmitted | AssignmentRejected | AssignmentApproved |
    -- HITCreated | HITExtended | HITDisposed | HITReviewable | HITExpired |
    -- Ping. The Ping event is only valid for the SendTestEventNotification
    -- operation.
    NotificationSpecification -> [EventType]
eventTypes :: [EventType]
  }
  deriving (NotificationSpecification -> NotificationSpecification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotificationSpecification -> NotificationSpecification -> Bool
$c/= :: NotificationSpecification -> NotificationSpecification -> Bool
== :: NotificationSpecification -> NotificationSpecification -> Bool
$c== :: NotificationSpecification -> NotificationSpecification -> Bool
Prelude.Eq, ReadPrec [NotificationSpecification]
ReadPrec NotificationSpecification
Int -> ReadS NotificationSpecification
ReadS [NotificationSpecification]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NotificationSpecification]
$creadListPrec :: ReadPrec [NotificationSpecification]
readPrec :: ReadPrec NotificationSpecification
$creadPrec :: ReadPrec NotificationSpecification
readList :: ReadS [NotificationSpecification]
$creadList :: ReadS [NotificationSpecification]
readsPrec :: Int -> ReadS NotificationSpecification
$creadsPrec :: Int -> ReadS NotificationSpecification
Prelude.Read, Int -> NotificationSpecification -> ShowS
[NotificationSpecification] -> ShowS
NotificationSpecification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotificationSpecification] -> ShowS
$cshowList :: [NotificationSpecification] -> ShowS
show :: NotificationSpecification -> String
$cshow :: NotificationSpecification -> String
showsPrec :: Int -> NotificationSpecification -> ShowS
$cshowsPrec :: Int -> NotificationSpecification -> ShowS
Prelude.Show, forall x.
Rep NotificationSpecification x -> NotificationSpecification
forall x.
NotificationSpecification -> Rep NotificationSpecification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep NotificationSpecification x -> NotificationSpecification
$cfrom :: forall x.
NotificationSpecification -> Rep NotificationSpecification x
Prelude.Generic)

-- |
-- Create a value of 'NotificationSpecification' 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:
--
-- 'destination', 'notificationSpecification_destination' - The target for notification messages. The Destination’s format is
-- determined by the specified Transport:
--
-- -   When Transport is Email, the Destination is your email address.
--
-- -   When Transport is SQS, the Destination is your queue URL.
--
-- -   When Transport is SNS, the Destination is the ARN of your topic.
--
-- 'transport', 'notificationSpecification_transport' - The method Amazon Mechanical Turk uses to send the notification. Valid
-- Values: Email | SQS | SNS.
--
-- 'version', 'notificationSpecification_version' - The version of the Notification API to use. Valid value is 2006-05-05.
--
-- 'eventTypes', 'notificationSpecification_eventTypes' - The list of events that should cause notifications to be sent. Valid
-- Values: AssignmentAccepted | AssignmentAbandoned | AssignmentReturned |
-- AssignmentSubmitted | AssignmentRejected | AssignmentApproved |
-- HITCreated | HITExtended | HITDisposed | HITReviewable | HITExpired |
-- Ping. The Ping event is only valid for the SendTestEventNotification
-- operation.
newNotificationSpecification ::
  -- | 'destination'
  Prelude.Text ->
  -- | 'transport'
  NotificationTransport ->
  -- | 'version'
  Prelude.Text ->
  NotificationSpecification
newNotificationSpecification :: Text -> NotificationTransport -> Text -> NotificationSpecification
newNotificationSpecification
  Text
pDestination_
  NotificationTransport
pTransport_
  Text
pVersion_ =
    NotificationSpecification'
      { $sel:destination:NotificationSpecification' :: Text
destination =
          Text
pDestination_,
        $sel:transport:NotificationSpecification' :: NotificationTransport
transport = NotificationTransport
pTransport_,
        $sel:version:NotificationSpecification' :: Text
version = Text
pVersion_,
        $sel:eventTypes:NotificationSpecification' :: [EventType]
eventTypes = forall a. Monoid a => a
Prelude.mempty
      }

-- | The target for notification messages. The Destination’s format is
-- determined by the specified Transport:
--
-- -   When Transport is Email, the Destination is your email address.
--
-- -   When Transport is SQS, the Destination is your queue URL.
--
-- -   When Transport is SNS, the Destination is the ARN of your topic.
notificationSpecification_destination :: Lens.Lens' NotificationSpecification Prelude.Text
notificationSpecification_destination :: Lens' NotificationSpecification Text
notificationSpecification_destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotificationSpecification' {Text
destination :: Text
$sel:destination:NotificationSpecification' :: NotificationSpecification -> Text
destination} -> Text
destination) (\s :: NotificationSpecification
s@NotificationSpecification' {} Text
a -> NotificationSpecification
s {$sel:destination:NotificationSpecification' :: Text
destination = Text
a} :: NotificationSpecification)

-- | The method Amazon Mechanical Turk uses to send the notification. Valid
-- Values: Email | SQS | SNS.
notificationSpecification_transport :: Lens.Lens' NotificationSpecification NotificationTransport
notificationSpecification_transport :: Lens' NotificationSpecification NotificationTransport
notificationSpecification_transport = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotificationSpecification' {NotificationTransport
transport :: NotificationTransport
$sel:transport:NotificationSpecification' :: NotificationSpecification -> NotificationTransport
transport} -> NotificationTransport
transport) (\s :: NotificationSpecification
s@NotificationSpecification' {} NotificationTransport
a -> NotificationSpecification
s {$sel:transport:NotificationSpecification' :: NotificationTransport
transport = NotificationTransport
a} :: NotificationSpecification)

-- | The version of the Notification API to use. Valid value is 2006-05-05.
notificationSpecification_version :: Lens.Lens' NotificationSpecification Prelude.Text
notificationSpecification_version :: Lens' NotificationSpecification Text
notificationSpecification_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotificationSpecification' {Text
version :: Text
$sel:version:NotificationSpecification' :: NotificationSpecification -> Text
version} -> Text
version) (\s :: NotificationSpecification
s@NotificationSpecification' {} Text
a -> NotificationSpecification
s {$sel:version:NotificationSpecification' :: Text
version = Text
a} :: NotificationSpecification)

-- | The list of events that should cause notifications to be sent. Valid
-- Values: AssignmentAccepted | AssignmentAbandoned | AssignmentReturned |
-- AssignmentSubmitted | AssignmentRejected | AssignmentApproved |
-- HITCreated | HITExtended | HITDisposed | HITReviewable | HITExpired |
-- Ping. The Ping event is only valid for the SendTestEventNotification
-- operation.
notificationSpecification_eventTypes :: Lens.Lens' NotificationSpecification [EventType]
notificationSpecification_eventTypes :: Lens' NotificationSpecification [EventType]
notificationSpecification_eventTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\NotificationSpecification' {[EventType]
eventTypes :: [EventType]
$sel:eventTypes:NotificationSpecification' :: NotificationSpecification -> [EventType]
eventTypes} -> [EventType]
eventTypes) (\s :: NotificationSpecification
s@NotificationSpecification' {} [EventType]
a -> NotificationSpecification
s {$sel:eventTypes:NotificationSpecification' :: [EventType]
eventTypes = [EventType]
a} :: NotificationSpecification) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Prelude.Hashable NotificationSpecification where
  hashWithSalt :: Int -> NotificationSpecification -> Int
hashWithSalt Int
_salt NotificationSpecification' {[EventType]
Text
NotificationTransport
eventTypes :: [EventType]
version :: Text
transport :: NotificationTransport
destination :: Text
$sel:eventTypes:NotificationSpecification' :: NotificationSpecification -> [EventType]
$sel:version:NotificationSpecification' :: NotificationSpecification -> Text
$sel:transport:NotificationSpecification' :: NotificationSpecification -> NotificationTransport
$sel:destination:NotificationSpecification' :: NotificationSpecification -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
destination
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NotificationTransport
transport
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
version
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [EventType]
eventTypes

instance Prelude.NFData NotificationSpecification where
  rnf :: NotificationSpecification -> ()
rnf NotificationSpecification' {[EventType]
Text
NotificationTransport
eventTypes :: [EventType]
version :: Text
transport :: NotificationTransport
destination :: Text
$sel:eventTypes:NotificationSpecification' :: NotificationSpecification -> [EventType]
$sel:version:NotificationSpecification' :: NotificationSpecification -> Text
$sel:transport:NotificationSpecification' :: NotificationSpecification -> NotificationTransport
$sel:destination:NotificationSpecification' :: NotificationSpecification -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
destination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NotificationTransport
transport
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [EventType]
eventTypes

instance Data.ToJSON NotificationSpecification where
  toJSON :: NotificationSpecification -> Value
toJSON NotificationSpecification' {[EventType]
Text
NotificationTransport
eventTypes :: [EventType]
version :: Text
transport :: NotificationTransport
destination :: Text
$sel:eventTypes:NotificationSpecification' :: NotificationSpecification -> [EventType]
$sel:version:NotificationSpecification' :: NotificationSpecification -> Text
$sel:transport:NotificationSpecification' :: NotificationSpecification -> NotificationTransport
$sel:destination:NotificationSpecification' :: NotificationSpecification -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"Destination" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
destination),
            forall a. a -> Maybe a
Prelude.Just (Key
"Transport" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NotificationTransport
transport),
            forall a. a -> Maybe a
Prelude.Just (Key
"Version" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
version),
            forall a. a -> Maybe a
Prelude.Just (Key
"EventTypes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [EventType]
eventTypes)
          ]
      )