{-# 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.Glue.StartExportLabelsTaskRun
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Begins an asynchronous task to export all labeled data for a particular
-- transform. This task is the only label-related API call that is not part
-- of the typical active learning workflow. You typically use
-- @StartExportLabelsTaskRun@ when you want to work with all of your
-- existing labels at the same time, such as when you want to remove or
-- change labels that were previously submitted as truth. This API
-- operation accepts the @TransformId@ whose labels you want to export and
-- an Amazon Simple Storage Service (Amazon S3) path to export the labels
-- to. The operation returns a @TaskRunId@. You can check on the status of
-- your task run by calling the @GetMLTaskRun@ API.
module Amazonka.Glue.StartExportLabelsTaskRun
  ( -- * Creating a Request
    StartExportLabelsTaskRun (..),
    newStartExportLabelsTaskRun,

    -- * Request Lenses
    startExportLabelsTaskRun_transformId,
    startExportLabelsTaskRun_outputS3Path,

    -- * Destructuring the Response
    StartExportLabelsTaskRunResponse (..),
    newStartExportLabelsTaskRunResponse,

    -- * Response Lenses
    startExportLabelsTaskRunResponse_taskRunId,
    startExportLabelsTaskRunResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStartExportLabelsTaskRun' smart constructor.
data StartExportLabelsTaskRun = StartExportLabelsTaskRun'
  { -- | The unique identifier of the machine learning transform.
    StartExportLabelsTaskRun -> Text
transformId :: Prelude.Text,
    -- | The Amazon S3 path where you export the labels.
    StartExportLabelsTaskRun -> Text
outputS3Path :: Prelude.Text
  }
  deriving (StartExportLabelsTaskRun -> StartExportLabelsTaskRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartExportLabelsTaskRun -> StartExportLabelsTaskRun -> Bool
$c/= :: StartExportLabelsTaskRun -> StartExportLabelsTaskRun -> Bool
== :: StartExportLabelsTaskRun -> StartExportLabelsTaskRun -> Bool
$c== :: StartExportLabelsTaskRun -> StartExportLabelsTaskRun -> Bool
Prelude.Eq, ReadPrec [StartExportLabelsTaskRun]
ReadPrec StartExportLabelsTaskRun
Int -> ReadS StartExportLabelsTaskRun
ReadS [StartExportLabelsTaskRun]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartExportLabelsTaskRun]
$creadListPrec :: ReadPrec [StartExportLabelsTaskRun]
readPrec :: ReadPrec StartExportLabelsTaskRun
$creadPrec :: ReadPrec StartExportLabelsTaskRun
readList :: ReadS [StartExportLabelsTaskRun]
$creadList :: ReadS [StartExportLabelsTaskRun]
readsPrec :: Int -> ReadS StartExportLabelsTaskRun
$creadsPrec :: Int -> ReadS StartExportLabelsTaskRun
Prelude.Read, Int -> StartExportLabelsTaskRun -> ShowS
[StartExportLabelsTaskRun] -> ShowS
StartExportLabelsTaskRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartExportLabelsTaskRun] -> ShowS
$cshowList :: [StartExportLabelsTaskRun] -> ShowS
show :: StartExportLabelsTaskRun -> String
$cshow :: StartExportLabelsTaskRun -> String
showsPrec :: Int -> StartExportLabelsTaskRun -> ShowS
$cshowsPrec :: Int -> StartExportLabelsTaskRun -> ShowS
Prelude.Show, forall x.
Rep StartExportLabelsTaskRun x -> StartExportLabelsTaskRun
forall x.
StartExportLabelsTaskRun -> Rep StartExportLabelsTaskRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartExportLabelsTaskRun x -> StartExportLabelsTaskRun
$cfrom :: forall x.
StartExportLabelsTaskRun -> Rep StartExportLabelsTaskRun x
Prelude.Generic)

-- |
-- Create a value of 'StartExportLabelsTaskRun' 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:
--
-- 'transformId', 'startExportLabelsTaskRun_transformId' - The unique identifier of the machine learning transform.
--
-- 'outputS3Path', 'startExportLabelsTaskRun_outputS3Path' - The Amazon S3 path where you export the labels.
newStartExportLabelsTaskRun ::
  -- | 'transformId'
  Prelude.Text ->
  -- | 'outputS3Path'
  Prelude.Text ->
  StartExportLabelsTaskRun
newStartExportLabelsTaskRun :: Text -> Text -> StartExportLabelsTaskRun
newStartExportLabelsTaskRun
  Text
pTransformId_
  Text
pOutputS3Path_ =
    StartExportLabelsTaskRun'
      { $sel:transformId:StartExportLabelsTaskRun' :: Text
transformId =
          Text
pTransformId_,
        $sel:outputS3Path:StartExportLabelsTaskRun' :: Text
outputS3Path = Text
pOutputS3Path_
      }

-- | The unique identifier of the machine learning transform.
startExportLabelsTaskRun_transformId :: Lens.Lens' StartExportLabelsTaskRun Prelude.Text
startExportLabelsTaskRun_transformId :: Lens' StartExportLabelsTaskRun Text
startExportLabelsTaskRun_transformId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartExportLabelsTaskRun' {Text
transformId :: Text
$sel:transformId:StartExportLabelsTaskRun' :: StartExportLabelsTaskRun -> Text
transformId} -> Text
transformId) (\s :: StartExportLabelsTaskRun
s@StartExportLabelsTaskRun' {} Text
a -> StartExportLabelsTaskRun
s {$sel:transformId:StartExportLabelsTaskRun' :: Text
transformId = Text
a} :: StartExportLabelsTaskRun)

-- | The Amazon S3 path where you export the labels.
startExportLabelsTaskRun_outputS3Path :: Lens.Lens' StartExportLabelsTaskRun Prelude.Text
startExportLabelsTaskRun_outputS3Path :: Lens' StartExportLabelsTaskRun Text
startExportLabelsTaskRun_outputS3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartExportLabelsTaskRun' {Text
outputS3Path :: Text
$sel:outputS3Path:StartExportLabelsTaskRun' :: StartExportLabelsTaskRun -> Text
outputS3Path} -> Text
outputS3Path) (\s :: StartExportLabelsTaskRun
s@StartExportLabelsTaskRun' {} Text
a -> StartExportLabelsTaskRun
s {$sel:outputS3Path:StartExportLabelsTaskRun' :: Text
outputS3Path = Text
a} :: StartExportLabelsTaskRun)

instance Core.AWSRequest StartExportLabelsTaskRun where
  type
    AWSResponse StartExportLabelsTaskRun =
      StartExportLabelsTaskRunResponse
  request :: (Service -> Service)
-> StartExportLabelsTaskRun -> Request StartExportLabelsTaskRun
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 StartExportLabelsTaskRun
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartExportLabelsTaskRun)))
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 Text -> Int -> StartExportLabelsTaskRunResponse
StartExportLabelsTaskRunResponse'
            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
"TaskRunId")
            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 StartExportLabelsTaskRun where
  hashWithSalt :: Int -> StartExportLabelsTaskRun -> Int
hashWithSalt Int
_salt StartExportLabelsTaskRun' {Text
outputS3Path :: Text
transformId :: Text
$sel:outputS3Path:StartExportLabelsTaskRun' :: StartExportLabelsTaskRun -> Text
$sel:transformId:StartExportLabelsTaskRun' :: StartExportLabelsTaskRun -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
transformId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
outputS3Path

instance Prelude.NFData StartExportLabelsTaskRun where
  rnf :: StartExportLabelsTaskRun -> ()
rnf StartExportLabelsTaskRun' {Text
outputS3Path :: Text
transformId :: Text
$sel:outputS3Path:StartExportLabelsTaskRun' :: StartExportLabelsTaskRun -> Text
$sel:transformId:StartExportLabelsTaskRun' :: StartExportLabelsTaskRun -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
transformId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
outputS3Path

instance Data.ToHeaders StartExportLabelsTaskRun where
  toHeaders :: StartExportLabelsTaskRun -> 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
"AWSGlue.StartExportLabelsTaskRun" ::
                          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 StartExportLabelsTaskRun where
  toJSON :: StartExportLabelsTaskRun -> Value
toJSON StartExportLabelsTaskRun' {Text
outputS3Path :: Text
transformId :: Text
$sel:outputS3Path:StartExportLabelsTaskRun' :: StartExportLabelsTaskRun -> Text
$sel:transformId:StartExportLabelsTaskRun' :: StartExportLabelsTaskRun -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"TransformId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
transformId),
            forall a. a -> Maybe a
Prelude.Just (Key
"OutputS3Path" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
outputS3Path)
          ]
      )

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

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

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

-- |
-- Create a value of 'StartExportLabelsTaskRunResponse' 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:
--
-- 'taskRunId', 'startExportLabelsTaskRunResponse_taskRunId' - The unique identifier for the task run.
--
-- 'httpStatus', 'startExportLabelsTaskRunResponse_httpStatus' - The response's http status code.
newStartExportLabelsTaskRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartExportLabelsTaskRunResponse
newStartExportLabelsTaskRunResponse :: Int -> StartExportLabelsTaskRunResponse
newStartExportLabelsTaskRunResponse Int
pHttpStatus_ =
  StartExportLabelsTaskRunResponse'
    { $sel:taskRunId:StartExportLabelsTaskRunResponse' :: Maybe Text
taskRunId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartExportLabelsTaskRunResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The unique identifier for the task run.
startExportLabelsTaskRunResponse_taskRunId :: Lens.Lens' StartExportLabelsTaskRunResponse (Prelude.Maybe Prelude.Text)
startExportLabelsTaskRunResponse_taskRunId :: Lens' StartExportLabelsTaskRunResponse (Maybe Text)
startExportLabelsTaskRunResponse_taskRunId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartExportLabelsTaskRunResponse' {Maybe Text
taskRunId :: Maybe Text
$sel:taskRunId:StartExportLabelsTaskRunResponse' :: StartExportLabelsTaskRunResponse -> Maybe Text
taskRunId} -> Maybe Text
taskRunId) (\s :: StartExportLabelsTaskRunResponse
s@StartExportLabelsTaskRunResponse' {} Maybe Text
a -> StartExportLabelsTaskRunResponse
s {$sel:taskRunId:StartExportLabelsTaskRunResponse' :: Maybe Text
taskRunId = Maybe Text
a} :: StartExportLabelsTaskRunResponse)

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

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