{-# 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.CreateImportJob
-- 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 an import job for an application.
module Amazonka.Pinpoint.CreateImportJob
  ( -- * Creating a Request
    CreateImportJob (..),
    newCreateImportJob,

    -- * Request Lenses
    createImportJob_applicationId,
    createImportJob_importJobRequest,

    -- * Destructuring the Response
    CreateImportJobResponse (..),
    newCreateImportJobResponse,

    -- * Response Lenses
    createImportJobResponse_httpStatus,
    createImportJobResponse_importJobResponse,
  )
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:/ 'newCreateImportJob' smart constructor.
data CreateImportJob = CreateImportJob'
  { -- | The unique identifier for the application. This identifier is displayed
    -- as the __Project ID__ on the Amazon Pinpoint console.
    CreateImportJob -> Text
applicationId :: Prelude.Text,
    CreateImportJob -> ImportJobRequest
importJobRequest :: ImportJobRequest
  }
  deriving (CreateImportJob -> CreateImportJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateImportJob -> CreateImportJob -> Bool
$c/= :: CreateImportJob -> CreateImportJob -> Bool
== :: CreateImportJob -> CreateImportJob -> Bool
$c== :: CreateImportJob -> CreateImportJob -> Bool
Prelude.Eq, ReadPrec [CreateImportJob]
ReadPrec CreateImportJob
Int -> ReadS CreateImportJob
ReadS [CreateImportJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateImportJob]
$creadListPrec :: ReadPrec [CreateImportJob]
readPrec :: ReadPrec CreateImportJob
$creadPrec :: ReadPrec CreateImportJob
readList :: ReadS [CreateImportJob]
$creadList :: ReadS [CreateImportJob]
readsPrec :: Int -> ReadS CreateImportJob
$creadsPrec :: Int -> ReadS CreateImportJob
Prelude.Read, Int -> CreateImportJob -> ShowS
[CreateImportJob] -> ShowS
CreateImportJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateImportJob] -> ShowS
$cshowList :: [CreateImportJob] -> ShowS
show :: CreateImportJob -> String
$cshow :: CreateImportJob -> String
showsPrec :: Int -> CreateImportJob -> ShowS
$cshowsPrec :: Int -> CreateImportJob -> ShowS
Prelude.Show, forall x. Rep CreateImportJob x -> CreateImportJob
forall x. CreateImportJob -> Rep CreateImportJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateImportJob x -> CreateImportJob
$cfrom :: forall x. CreateImportJob -> Rep CreateImportJob x
Prelude.Generic)

-- |
-- Create a value of 'CreateImportJob' 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', 'createImportJob_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
--
-- 'importJobRequest', 'createImportJob_importJobRequest' - Undocumented member.
newCreateImportJob ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'importJobRequest'
  ImportJobRequest ->
  CreateImportJob
newCreateImportJob :: Text -> ImportJobRequest -> CreateImportJob
newCreateImportJob Text
pApplicationId_ ImportJobRequest
pImportJobRequest_ =
  CreateImportJob'
    { $sel:applicationId:CreateImportJob' :: Text
applicationId = Text
pApplicationId_,
      $sel:importJobRequest:CreateImportJob' :: ImportJobRequest
importJobRequest = ImportJobRequest
pImportJobRequest_
    }

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

-- | Undocumented member.
createImportJob_importJobRequest :: Lens.Lens' CreateImportJob ImportJobRequest
createImportJob_importJobRequest :: Lens' CreateImportJob ImportJobRequest
createImportJob_importJobRequest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImportJob' {ImportJobRequest
importJobRequest :: ImportJobRequest
$sel:importJobRequest:CreateImportJob' :: CreateImportJob -> ImportJobRequest
importJobRequest} -> ImportJobRequest
importJobRequest) (\s :: CreateImportJob
s@CreateImportJob' {} ImportJobRequest
a -> CreateImportJob
s {$sel:importJobRequest:CreateImportJob' :: ImportJobRequest
importJobRequest = ImportJobRequest
a} :: CreateImportJob)

instance Core.AWSRequest CreateImportJob where
  type
    AWSResponse CreateImportJob =
      CreateImportJobResponse
  request :: (Service -> Service) -> CreateImportJob -> Request CreateImportJob
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 CreateImportJob
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateImportJob)))
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 -> ImportJobResponse -> CreateImportJobResponse
CreateImportJobResponse'
            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 CreateImportJob where
  hashWithSalt :: Int -> CreateImportJob -> Int
hashWithSalt Int
_salt CreateImportJob' {Text
ImportJobRequest
importJobRequest :: ImportJobRequest
applicationId :: Text
$sel:importJobRequest:CreateImportJob' :: CreateImportJob -> ImportJobRequest
$sel:applicationId:CreateImportJob' :: CreateImportJob -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ImportJobRequest
importJobRequest

instance Prelude.NFData CreateImportJob where
  rnf :: CreateImportJob -> ()
rnf CreateImportJob' {Text
ImportJobRequest
importJobRequest :: ImportJobRequest
applicationId :: Text
$sel:importJobRequest:CreateImportJob' :: CreateImportJob -> ImportJobRequest
$sel:applicationId:CreateImportJob' :: CreateImportJob -> 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 ImportJobRequest
importJobRequest

instance Data.ToHeaders CreateImportJob where
  toHeaders :: CreateImportJob -> 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 CreateImportJob where
  toJSON :: CreateImportJob -> Value
toJSON CreateImportJob' {Text
ImportJobRequest
importJobRequest :: ImportJobRequest
applicationId :: Text
$sel:importJobRequest:CreateImportJob' :: CreateImportJob -> ImportJobRequest
$sel:applicationId:CreateImportJob' :: CreateImportJob -> Text
..} =
    forall a. ToJSON a => a -> Value
Data.toJSON ImportJobRequest
importJobRequest

instance Data.ToPath CreateImportJob where
  toPath :: CreateImportJob -> ByteString
toPath CreateImportJob' {Text
ImportJobRequest
importJobRequest :: ImportJobRequest
applicationId :: Text
$sel:importJobRequest:CreateImportJob' :: CreateImportJob -> ImportJobRequest
$sel:applicationId:CreateImportJob' :: CreateImportJob -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/jobs/import"
      ]

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

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

-- |
-- Create a value of 'CreateImportJobResponse' 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', 'createImportJobResponse_httpStatus' - The response's http status code.
--
-- 'importJobResponse', 'createImportJobResponse_importJobResponse' - Undocumented member.
newCreateImportJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'importJobResponse'
  ImportJobResponse ->
  CreateImportJobResponse
newCreateImportJobResponse :: Int -> ImportJobResponse -> CreateImportJobResponse
newCreateImportJobResponse
  Int
pHttpStatus_
  ImportJobResponse
pImportJobResponse_ =
    CreateImportJobResponse'
      { $sel:httpStatus:CreateImportJobResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:importJobResponse:CreateImportJobResponse' :: ImportJobResponse
importJobResponse = ImportJobResponse
pImportJobResponse_
      }

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

-- | Undocumented member.
createImportJobResponse_importJobResponse :: Lens.Lens' CreateImportJobResponse ImportJobResponse
createImportJobResponse_importJobResponse :: Lens' CreateImportJobResponse ImportJobResponse
createImportJobResponse_importJobResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateImportJobResponse' {ImportJobResponse
importJobResponse :: ImportJobResponse
$sel:importJobResponse:CreateImportJobResponse' :: CreateImportJobResponse -> ImportJobResponse
importJobResponse} -> ImportJobResponse
importJobResponse) (\s :: CreateImportJobResponse
s@CreateImportJobResponse' {} ImportJobResponse
a -> CreateImportJobResponse
s {$sel:importJobResponse:CreateImportJobResponse' :: ImportJobResponse
importJobResponse = ImportJobResponse
a} :: CreateImportJobResponse)

instance Prelude.NFData CreateImportJobResponse where
  rnf :: CreateImportJobResponse -> ()
rnf CreateImportJobResponse' {Int
ImportJobResponse
importJobResponse :: ImportJobResponse
httpStatus :: Int
$sel:importJobResponse:CreateImportJobResponse' :: CreateImportJobResponse -> ImportJobResponse
$sel:httpStatus:CreateImportJobResponse' :: CreateImportJobResponse -> 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 ImportJobResponse
importJobResponse