{-# 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.Pinpoint.PutEvents
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new event to record for endpoints, or creates or updates
-- endpoint data that existing events are associated with.
module Amazonka.Pinpoint.PutEvents
  ( -- * Creating a Request
    PutEvents (..),
    newPutEvents,

    -- * Request Lenses
    putEvents_applicationId,
    putEvents_eventsRequest,

    -- * Destructuring the Response
    PutEventsResponse (..),
    newPutEventsResponse,

    -- * Response Lenses
    putEventsResponse_httpStatus,
    putEventsResponse_eventsResponse,
  )
where

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

-- | /See:/ 'newPutEvents' smart constructor.
data PutEvents = PutEvents'
  { -- | The unique identifier for the application. This identifier is displayed
    -- as the __Project ID__ on the Amazon Pinpoint console.
    PutEvents -> Text
applicationId :: Prelude.Text,
    PutEvents -> EventsRequest
eventsRequest :: EventsRequest
  }
  deriving (PutEvents -> PutEvents -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutEvents -> PutEvents -> Bool
$c/= :: PutEvents -> PutEvents -> Bool
== :: PutEvents -> PutEvents -> Bool
$c== :: PutEvents -> PutEvents -> Bool
Prelude.Eq, ReadPrec [PutEvents]
ReadPrec PutEvents
Int -> ReadS PutEvents
ReadS [PutEvents]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutEvents]
$creadListPrec :: ReadPrec [PutEvents]
readPrec :: ReadPrec PutEvents
$creadPrec :: ReadPrec PutEvents
readList :: ReadS [PutEvents]
$creadList :: ReadS [PutEvents]
readsPrec :: Int -> ReadS PutEvents
$creadsPrec :: Int -> ReadS PutEvents
Prelude.Read, Int -> PutEvents -> ShowS
[PutEvents] -> ShowS
PutEvents -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutEvents] -> ShowS
$cshowList :: [PutEvents] -> ShowS
show :: PutEvents -> String
$cshow :: PutEvents -> String
showsPrec :: Int -> PutEvents -> ShowS
$cshowsPrec :: Int -> PutEvents -> ShowS
Prelude.Show, forall x. Rep PutEvents x -> PutEvents
forall x. PutEvents -> Rep PutEvents x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutEvents x -> PutEvents
$cfrom :: forall x. PutEvents -> Rep PutEvents x
Prelude.Generic)

-- |
-- Create a value of 'PutEvents' 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:
--
-- 'applicationId', 'putEvents_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
--
-- 'eventsRequest', 'putEvents_eventsRequest' - Undocumented member.
newPutEvents ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'eventsRequest'
  EventsRequest ->
  PutEvents
newPutEvents :: Text -> EventsRequest -> PutEvents
newPutEvents Text
pApplicationId_ EventsRequest
pEventsRequest_ =
  PutEvents'
    { $sel:applicationId:PutEvents' :: Text
applicationId = Text
pApplicationId_,
      $sel:eventsRequest:PutEvents' :: EventsRequest
eventsRequest = EventsRequest
pEventsRequest_
    }

-- | The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
putEvents_applicationId :: Lens.Lens' PutEvents Prelude.Text
putEvents_applicationId :: Lens' PutEvents Text
putEvents_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutEvents' {Text
applicationId :: Text
$sel:applicationId:PutEvents' :: PutEvents -> Text
applicationId} -> Text
applicationId) (\s :: PutEvents
s@PutEvents' {} Text
a -> PutEvents
s {$sel:applicationId:PutEvents' :: Text
applicationId = Text
a} :: PutEvents)

-- | Undocumented member.
putEvents_eventsRequest :: Lens.Lens' PutEvents EventsRequest
putEvents_eventsRequest :: Lens' PutEvents EventsRequest
putEvents_eventsRequest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutEvents' {EventsRequest
eventsRequest :: EventsRequest
$sel:eventsRequest:PutEvents' :: PutEvents -> EventsRequest
eventsRequest} -> EventsRequest
eventsRequest) (\s :: PutEvents
s@PutEvents' {} EventsRequest
a -> PutEvents
s {$sel:eventsRequest:PutEvents' :: EventsRequest
eventsRequest = EventsRequest
a} :: PutEvents)

instance Core.AWSRequest PutEvents where
  type AWSResponse PutEvents = PutEventsResponse
  request :: (Service -> Service) -> PutEvents -> Request PutEvents
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 PutEvents
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PutEvents)))
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 ->
          Int -> EventsResponse -> PutEventsResponse
PutEventsResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
      )

instance Prelude.Hashable PutEvents where
  hashWithSalt :: Int -> PutEvents -> Int
hashWithSalt Int
_salt PutEvents' {Text
EventsRequest
eventsRequest :: EventsRequest
applicationId :: Text
$sel:eventsRequest:PutEvents' :: PutEvents -> EventsRequest
$sel:applicationId:PutEvents' :: PutEvents -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` EventsRequest
eventsRequest

instance Prelude.NFData PutEvents where
  rnf :: PutEvents -> ()
rnf PutEvents' {Text
EventsRequest
eventsRequest :: EventsRequest
applicationId :: Text
$sel:eventsRequest:PutEvents' :: PutEvents -> EventsRequest
$sel:applicationId:PutEvents' :: PutEvents -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf EventsRequest
eventsRequest

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

instance Data.ToJSON PutEvents where
  toJSON :: PutEvents -> Value
toJSON PutEvents' {Text
EventsRequest
eventsRequest :: EventsRequest
applicationId :: Text
$sel:eventsRequest:PutEvents' :: PutEvents -> EventsRequest
$sel:applicationId:PutEvents' :: PutEvents -> Text
..} = forall a. ToJSON a => a -> Value
Data.toJSON EventsRequest
eventsRequest

instance Data.ToPath PutEvents where
  toPath :: PutEvents -> ByteString
toPath PutEvents' {Text
EventsRequest
eventsRequest :: EventsRequest
applicationId :: Text
$sel:eventsRequest:PutEvents' :: PutEvents -> EventsRequest
$sel:applicationId:PutEvents' :: PutEvents -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/apps/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId, ByteString
"/events"]

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

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

-- |
-- Create a value of 'PutEventsResponse' 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:
--
-- 'httpStatus', 'putEventsResponse_httpStatus' - The response's http status code.
--
-- 'eventsResponse', 'putEventsResponse_eventsResponse' - Undocumented member.
newPutEventsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'eventsResponse'
  EventsResponse ->
  PutEventsResponse
newPutEventsResponse :: Int -> EventsResponse -> PutEventsResponse
newPutEventsResponse Int
pHttpStatus_ EventsResponse
pEventsResponse_ =
  PutEventsResponse'
    { $sel:httpStatus:PutEventsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:eventsResponse:PutEventsResponse' :: EventsResponse
eventsResponse = EventsResponse
pEventsResponse_
    }

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

-- | Undocumented member.
putEventsResponse_eventsResponse :: Lens.Lens' PutEventsResponse EventsResponse
putEventsResponse_eventsResponse :: Lens' PutEventsResponse EventsResponse
putEventsResponse_eventsResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutEventsResponse' {EventsResponse
eventsResponse :: EventsResponse
$sel:eventsResponse:PutEventsResponse' :: PutEventsResponse -> EventsResponse
eventsResponse} -> EventsResponse
eventsResponse) (\s :: PutEventsResponse
s@PutEventsResponse' {} EventsResponse
a -> PutEventsResponse
s {$sel:eventsResponse:PutEventsResponse' :: EventsResponse
eventsResponse = EventsResponse
a} :: PutEventsResponse)

instance Prelude.NFData PutEventsResponse where
  rnf :: PutEventsResponse -> ()
rnf PutEventsResponse' {Int
EventsResponse
eventsResponse :: EventsResponse
httpStatus :: Int
$sel:eventsResponse:PutEventsResponse' :: PutEventsResponse -> EventsResponse
$sel:httpStatus:PutEventsResponse' :: PutEventsResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf EventsResponse
eventsResponse