{-# 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.CognitoIdentityProvider.StartUserImportJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts the user import.
module Amazonka.CognitoIdentityProvider.StartUserImportJob
  ( -- * Creating a Request
    StartUserImportJob (..),
    newStartUserImportJob,

    -- * Request Lenses
    startUserImportJob_userPoolId,
    startUserImportJob_jobId,

    -- * Destructuring the Response
    StartUserImportJobResponse (..),
    newStartUserImportJobResponse,

    -- * Response Lenses
    startUserImportJobResponse_userImportJob,
    startUserImportJobResponse_httpStatus,
  )
where

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

-- | Represents the request to start the user import job.
--
-- /See:/ 'newStartUserImportJob' smart constructor.
data StartUserImportJob = StartUserImportJob'
  { -- | The user pool ID for the user pool that the users are being imported
    -- into.
    StartUserImportJob -> Text
userPoolId :: Prelude.Text,
    -- | The job ID for the user import job.
    StartUserImportJob -> Text
jobId :: Prelude.Text
  }
  deriving (StartUserImportJob -> StartUserImportJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartUserImportJob -> StartUserImportJob -> Bool
$c/= :: StartUserImportJob -> StartUserImportJob -> Bool
== :: StartUserImportJob -> StartUserImportJob -> Bool
$c== :: StartUserImportJob -> StartUserImportJob -> Bool
Prelude.Eq, ReadPrec [StartUserImportJob]
ReadPrec StartUserImportJob
Int -> ReadS StartUserImportJob
ReadS [StartUserImportJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartUserImportJob]
$creadListPrec :: ReadPrec [StartUserImportJob]
readPrec :: ReadPrec StartUserImportJob
$creadPrec :: ReadPrec StartUserImportJob
readList :: ReadS [StartUserImportJob]
$creadList :: ReadS [StartUserImportJob]
readsPrec :: Int -> ReadS StartUserImportJob
$creadsPrec :: Int -> ReadS StartUserImportJob
Prelude.Read, Int -> StartUserImportJob -> ShowS
[StartUserImportJob] -> ShowS
StartUserImportJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartUserImportJob] -> ShowS
$cshowList :: [StartUserImportJob] -> ShowS
show :: StartUserImportJob -> String
$cshow :: StartUserImportJob -> String
showsPrec :: Int -> StartUserImportJob -> ShowS
$cshowsPrec :: Int -> StartUserImportJob -> ShowS
Prelude.Show, forall x. Rep StartUserImportJob x -> StartUserImportJob
forall x. StartUserImportJob -> Rep StartUserImportJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartUserImportJob x -> StartUserImportJob
$cfrom :: forall x. StartUserImportJob -> Rep StartUserImportJob x
Prelude.Generic)

-- |
-- Create a value of 'StartUserImportJob' 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:
--
-- 'userPoolId', 'startUserImportJob_userPoolId' - The user pool ID for the user pool that the users are being imported
-- into.
--
-- 'jobId', 'startUserImportJob_jobId' - The job ID for the user import job.
newStartUserImportJob ::
  -- | 'userPoolId'
  Prelude.Text ->
  -- | 'jobId'
  Prelude.Text ->
  StartUserImportJob
newStartUserImportJob :: Text -> Text -> StartUserImportJob
newStartUserImportJob Text
pUserPoolId_ Text
pJobId_ =
  StartUserImportJob'
    { $sel:userPoolId:StartUserImportJob' :: Text
userPoolId = Text
pUserPoolId_,
      $sel:jobId:StartUserImportJob' :: Text
jobId = Text
pJobId_
    }

-- | The user pool ID for the user pool that the users are being imported
-- into.
startUserImportJob_userPoolId :: Lens.Lens' StartUserImportJob Prelude.Text
startUserImportJob_userPoolId :: Lens' StartUserImportJob Text
startUserImportJob_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartUserImportJob' {Text
userPoolId :: Text
$sel:userPoolId:StartUserImportJob' :: StartUserImportJob -> Text
userPoolId} -> Text
userPoolId) (\s :: StartUserImportJob
s@StartUserImportJob' {} Text
a -> StartUserImportJob
s {$sel:userPoolId:StartUserImportJob' :: Text
userPoolId = Text
a} :: StartUserImportJob)

-- | The job ID for the user import job.
startUserImportJob_jobId :: Lens.Lens' StartUserImportJob Prelude.Text
startUserImportJob_jobId :: Lens' StartUserImportJob Text
startUserImportJob_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartUserImportJob' {Text
jobId :: Text
$sel:jobId:StartUserImportJob' :: StartUserImportJob -> Text
jobId} -> Text
jobId) (\s :: StartUserImportJob
s@StartUserImportJob' {} Text
a -> StartUserImportJob
s {$sel:jobId:StartUserImportJob' :: Text
jobId = Text
a} :: StartUserImportJob)

instance Core.AWSRequest StartUserImportJob where
  type
    AWSResponse StartUserImportJob =
      StartUserImportJobResponse
  request :: (Service -> Service)
-> StartUserImportJob -> Request StartUserImportJob
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 StartUserImportJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartUserImportJob)))
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 UserImportJobType -> Int -> StartUserImportJobResponse
StartUserImportJobResponse'
            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
"UserImportJob")
            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 StartUserImportJob where
  hashWithSalt :: Int -> StartUserImportJob -> Int
hashWithSalt Int
_salt StartUserImportJob' {Text
jobId :: Text
userPoolId :: Text
$sel:jobId:StartUserImportJob' :: StartUserImportJob -> Text
$sel:userPoolId:StartUserImportJob' :: StartUserImportJob -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

instance Prelude.NFData StartUserImportJob where
  rnf :: StartUserImportJob -> ()
rnf StartUserImportJob' {Text
jobId :: Text
userPoolId :: Text
$sel:jobId:StartUserImportJob' :: StartUserImportJob -> Text
$sel:userPoolId:StartUserImportJob' :: StartUserImportJob -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
userPoolId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobId

instance Data.ToHeaders StartUserImportJob where
  toHeaders :: StartUserImportJob -> 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
"AWSCognitoIdentityProviderService.StartUserImportJob" ::
                          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 StartUserImportJob where
  toJSON :: StartUserImportJob -> Value
toJSON StartUserImportJob' {Text
jobId :: Text
userPoolId :: Text
$sel:jobId:StartUserImportJob' :: StartUserImportJob -> Text
$sel:userPoolId:StartUserImportJob' :: StartUserImportJob -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"UserPoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userPoolId),
            forall a. a -> Maybe a
Prelude.Just (Key
"JobId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobId)
          ]
      )

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

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

-- | Represents the response from the server to the request to start the user
-- import job.
--
-- /See:/ 'newStartUserImportJobResponse' smart constructor.
data StartUserImportJobResponse = StartUserImportJobResponse'
  { -- | The job object that represents the user import job.
    StartUserImportJobResponse -> Maybe UserImportJobType
userImportJob :: Prelude.Maybe UserImportJobType,
    -- | The response's http status code.
    StartUserImportJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartUserImportJobResponse -> StartUserImportJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartUserImportJobResponse -> StartUserImportJobResponse -> Bool
$c/= :: StartUserImportJobResponse -> StartUserImportJobResponse -> Bool
== :: StartUserImportJobResponse -> StartUserImportJobResponse -> Bool
$c== :: StartUserImportJobResponse -> StartUserImportJobResponse -> Bool
Prelude.Eq, ReadPrec [StartUserImportJobResponse]
ReadPrec StartUserImportJobResponse
Int -> ReadS StartUserImportJobResponse
ReadS [StartUserImportJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartUserImportJobResponse]
$creadListPrec :: ReadPrec [StartUserImportJobResponse]
readPrec :: ReadPrec StartUserImportJobResponse
$creadPrec :: ReadPrec StartUserImportJobResponse
readList :: ReadS [StartUserImportJobResponse]
$creadList :: ReadS [StartUserImportJobResponse]
readsPrec :: Int -> ReadS StartUserImportJobResponse
$creadsPrec :: Int -> ReadS StartUserImportJobResponse
Prelude.Read, Int -> StartUserImportJobResponse -> ShowS
[StartUserImportJobResponse] -> ShowS
StartUserImportJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartUserImportJobResponse] -> ShowS
$cshowList :: [StartUserImportJobResponse] -> ShowS
show :: StartUserImportJobResponse -> String
$cshow :: StartUserImportJobResponse -> String
showsPrec :: Int -> StartUserImportJobResponse -> ShowS
$cshowsPrec :: Int -> StartUserImportJobResponse -> ShowS
Prelude.Show, forall x.
Rep StartUserImportJobResponse x -> StartUserImportJobResponse
forall x.
StartUserImportJobResponse -> Rep StartUserImportJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartUserImportJobResponse x -> StartUserImportJobResponse
$cfrom :: forall x.
StartUserImportJobResponse -> Rep StartUserImportJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartUserImportJobResponse' 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:
--
-- 'userImportJob', 'startUserImportJobResponse_userImportJob' - The job object that represents the user import job.
--
-- 'httpStatus', 'startUserImportJobResponse_httpStatus' - The response's http status code.
newStartUserImportJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartUserImportJobResponse
newStartUserImportJobResponse :: Int -> StartUserImportJobResponse
newStartUserImportJobResponse Int
pHttpStatus_ =
  StartUserImportJobResponse'
    { $sel:userImportJob:StartUserImportJobResponse' :: Maybe UserImportJobType
userImportJob =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartUserImportJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The job object that represents the user import job.
startUserImportJobResponse_userImportJob :: Lens.Lens' StartUserImportJobResponse (Prelude.Maybe UserImportJobType)
startUserImportJobResponse_userImportJob :: Lens' StartUserImportJobResponse (Maybe UserImportJobType)
startUserImportJobResponse_userImportJob = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartUserImportJobResponse' {Maybe UserImportJobType
userImportJob :: Maybe UserImportJobType
$sel:userImportJob:StartUserImportJobResponse' :: StartUserImportJobResponse -> Maybe UserImportJobType
userImportJob} -> Maybe UserImportJobType
userImportJob) (\s :: StartUserImportJobResponse
s@StartUserImportJobResponse' {} Maybe UserImportJobType
a -> StartUserImportJobResponse
s {$sel:userImportJob:StartUserImportJobResponse' :: Maybe UserImportJobType
userImportJob = Maybe UserImportJobType
a} :: StartUserImportJobResponse)

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

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