{-# 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.Snowball.CreateReturnShippingLabel
-- 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 shipping label that will be used to return the Snow device to
-- Amazon Web Services.
module Amazonka.Snowball.CreateReturnShippingLabel
  ( -- * Creating a Request
    CreateReturnShippingLabel (..),
    newCreateReturnShippingLabel,

    -- * Request Lenses
    createReturnShippingLabel_shippingOption,
    createReturnShippingLabel_jobId,

    -- * Destructuring the Response
    CreateReturnShippingLabelResponse (..),
    newCreateReturnShippingLabelResponse,

    -- * Response Lenses
    createReturnShippingLabelResponse_status,
    createReturnShippingLabelResponse_httpStatus,
  )
where

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
import Amazonka.Snowball.Types

-- | /See:/ 'newCreateReturnShippingLabel' smart constructor.
data CreateReturnShippingLabel = CreateReturnShippingLabel'
  { -- | The shipping speed for a particular job. This speed doesn\'t dictate how
    -- soon the device is returned to Amazon Web Services. This speed
    -- represents how quickly it moves to its destination while in transit.
    -- Regional shipping speeds are as follows:
    CreateReturnShippingLabel -> Maybe ShippingOption
shippingOption :: Prelude.Maybe ShippingOption,
    -- | The ID for a job that you want to create the return shipping label for;
    -- for example, @JID123e4567-e89b-12d3-a456-426655440000@.
    CreateReturnShippingLabel -> Text
jobId :: Prelude.Text
  }
  deriving (CreateReturnShippingLabel -> CreateReturnShippingLabel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateReturnShippingLabel -> CreateReturnShippingLabel -> Bool
$c/= :: CreateReturnShippingLabel -> CreateReturnShippingLabel -> Bool
== :: CreateReturnShippingLabel -> CreateReturnShippingLabel -> Bool
$c== :: CreateReturnShippingLabel -> CreateReturnShippingLabel -> Bool
Prelude.Eq, ReadPrec [CreateReturnShippingLabel]
ReadPrec CreateReturnShippingLabel
Int -> ReadS CreateReturnShippingLabel
ReadS [CreateReturnShippingLabel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateReturnShippingLabel]
$creadListPrec :: ReadPrec [CreateReturnShippingLabel]
readPrec :: ReadPrec CreateReturnShippingLabel
$creadPrec :: ReadPrec CreateReturnShippingLabel
readList :: ReadS [CreateReturnShippingLabel]
$creadList :: ReadS [CreateReturnShippingLabel]
readsPrec :: Int -> ReadS CreateReturnShippingLabel
$creadsPrec :: Int -> ReadS CreateReturnShippingLabel
Prelude.Read, Int -> CreateReturnShippingLabel -> ShowS
[CreateReturnShippingLabel] -> ShowS
CreateReturnShippingLabel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateReturnShippingLabel] -> ShowS
$cshowList :: [CreateReturnShippingLabel] -> ShowS
show :: CreateReturnShippingLabel -> String
$cshow :: CreateReturnShippingLabel -> String
showsPrec :: Int -> CreateReturnShippingLabel -> ShowS
$cshowsPrec :: Int -> CreateReturnShippingLabel -> ShowS
Prelude.Show, forall x.
Rep CreateReturnShippingLabel x -> CreateReturnShippingLabel
forall x.
CreateReturnShippingLabel -> Rep CreateReturnShippingLabel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateReturnShippingLabel x -> CreateReturnShippingLabel
$cfrom :: forall x.
CreateReturnShippingLabel -> Rep CreateReturnShippingLabel x
Prelude.Generic)

-- |
-- Create a value of 'CreateReturnShippingLabel' 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:
--
-- 'shippingOption', 'createReturnShippingLabel_shippingOption' - The shipping speed for a particular job. This speed doesn\'t dictate how
-- soon the device is returned to Amazon Web Services. This speed
-- represents how quickly it moves to its destination while in transit.
-- Regional shipping speeds are as follows:
--
-- 'jobId', 'createReturnShippingLabel_jobId' - The ID for a job that you want to create the return shipping label for;
-- for example, @JID123e4567-e89b-12d3-a456-426655440000@.
newCreateReturnShippingLabel ::
  -- | 'jobId'
  Prelude.Text ->
  CreateReturnShippingLabel
newCreateReturnShippingLabel :: Text -> CreateReturnShippingLabel
newCreateReturnShippingLabel Text
pJobId_ =
  CreateReturnShippingLabel'
    { $sel:shippingOption:CreateReturnShippingLabel' :: Maybe ShippingOption
shippingOption =
        forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:CreateReturnShippingLabel' :: Text
jobId = Text
pJobId_
    }

-- | The shipping speed for a particular job. This speed doesn\'t dictate how
-- soon the device is returned to Amazon Web Services. This speed
-- represents how quickly it moves to its destination while in transit.
-- Regional shipping speeds are as follows:
createReturnShippingLabel_shippingOption :: Lens.Lens' CreateReturnShippingLabel (Prelude.Maybe ShippingOption)
createReturnShippingLabel_shippingOption :: Lens' CreateReturnShippingLabel (Maybe ShippingOption)
createReturnShippingLabel_shippingOption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateReturnShippingLabel' {Maybe ShippingOption
shippingOption :: Maybe ShippingOption
$sel:shippingOption:CreateReturnShippingLabel' :: CreateReturnShippingLabel -> Maybe ShippingOption
shippingOption} -> Maybe ShippingOption
shippingOption) (\s :: CreateReturnShippingLabel
s@CreateReturnShippingLabel' {} Maybe ShippingOption
a -> CreateReturnShippingLabel
s {$sel:shippingOption:CreateReturnShippingLabel' :: Maybe ShippingOption
shippingOption = Maybe ShippingOption
a} :: CreateReturnShippingLabel)

-- | The ID for a job that you want to create the return shipping label for;
-- for example, @JID123e4567-e89b-12d3-a456-426655440000@.
createReturnShippingLabel_jobId :: Lens.Lens' CreateReturnShippingLabel Prelude.Text
createReturnShippingLabel_jobId :: Lens' CreateReturnShippingLabel Text
createReturnShippingLabel_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateReturnShippingLabel' {Text
jobId :: Text
$sel:jobId:CreateReturnShippingLabel' :: CreateReturnShippingLabel -> Text
jobId} -> Text
jobId) (\s :: CreateReturnShippingLabel
s@CreateReturnShippingLabel' {} Text
a -> CreateReturnShippingLabel
s {$sel:jobId:CreateReturnShippingLabel' :: Text
jobId = Text
a} :: CreateReturnShippingLabel)

instance Core.AWSRequest CreateReturnShippingLabel where
  type
    AWSResponse CreateReturnShippingLabel =
      CreateReturnShippingLabelResponse
  request :: (Service -> Service)
-> CreateReturnShippingLabel -> Request CreateReturnShippingLabel
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 CreateReturnShippingLabel
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateReturnShippingLabel)))
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 ShippingLabelStatus
-> Int -> CreateReturnShippingLabelResponse
CreateReturnShippingLabelResponse'
            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
"Status")
            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 CreateReturnShippingLabel where
  hashWithSalt :: Int -> CreateReturnShippingLabel -> Int
hashWithSalt Int
_salt CreateReturnShippingLabel' {Maybe ShippingOption
Text
jobId :: Text
shippingOption :: Maybe ShippingOption
$sel:jobId:CreateReturnShippingLabel' :: CreateReturnShippingLabel -> Text
$sel:shippingOption:CreateReturnShippingLabel' :: CreateReturnShippingLabel -> Maybe ShippingOption
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ShippingOption
shippingOption
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

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

instance Data.ToHeaders CreateReturnShippingLabel where
  toHeaders :: CreateReturnShippingLabel -> 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
"AWSIESnowballJobManagementService.CreateReturnShippingLabel" ::
                          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 CreateReturnShippingLabel where
  toJSON :: CreateReturnShippingLabel -> Value
toJSON CreateReturnShippingLabel' {Maybe ShippingOption
Text
jobId :: Text
shippingOption :: Maybe ShippingOption
$sel:jobId:CreateReturnShippingLabel' :: CreateReturnShippingLabel -> Text
$sel:shippingOption:CreateReturnShippingLabel' :: CreateReturnShippingLabel -> Maybe ShippingOption
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ShippingOption" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ShippingOption
shippingOption,
            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 CreateReturnShippingLabel where
  toPath :: CreateReturnShippingLabel -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newCreateReturnShippingLabelResponse' smart constructor.
data CreateReturnShippingLabelResponse = CreateReturnShippingLabelResponse'
  { -- | The status information of the task on a Snow device that is being
    -- returned to Amazon Web Services.
    CreateReturnShippingLabelResponse -> Maybe ShippingLabelStatus
status :: Prelude.Maybe ShippingLabelStatus,
    -- | The response's http status code.
    CreateReturnShippingLabelResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateReturnShippingLabelResponse
-> CreateReturnShippingLabelResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateReturnShippingLabelResponse
-> CreateReturnShippingLabelResponse -> Bool
$c/= :: CreateReturnShippingLabelResponse
-> CreateReturnShippingLabelResponse -> Bool
== :: CreateReturnShippingLabelResponse
-> CreateReturnShippingLabelResponse -> Bool
$c== :: CreateReturnShippingLabelResponse
-> CreateReturnShippingLabelResponse -> Bool
Prelude.Eq, ReadPrec [CreateReturnShippingLabelResponse]
ReadPrec CreateReturnShippingLabelResponse
Int -> ReadS CreateReturnShippingLabelResponse
ReadS [CreateReturnShippingLabelResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateReturnShippingLabelResponse]
$creadListPrec :: ReadPrec [CreateReturnShippingLabelResponse]
readPrec :: ReadPrec CreateReturnShippingLabelResponse
$creadPrec :: ReadPrec CreateReturnShippingLabelResponse
readList :: ReadS [CreateReturnShippingLabelResponse]
$creadList :: ReadS [CreateReturnShippingLabelResponse]
readsPrec :: Int -> ReadS CreateReturnShippingLabelResponse
$creadsPrec :: Int -> ReadS CreateReturnShippingLabelResponse
Prelude.Read, Int -> CreateReturnShippingLabelResponse -> ShowS
[CreateReturnShippingLabelResponse] -> ShowS
CreateReturnShippingLabelResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateReturnShippingLabelResponse] -> ShowS
$cshowList :: [CreateReturnShippingLabelResponse] -> ShowS
show :: CreateReturnShippingLabelResponse -> String
$cshow :: CreateReturnShippingLabelResponse -> String
showsPrec :: Int -> CreateReturnShippingLabelResponse -> ShowS
$cshowsPrec :: Int -> CreateReturnShippingLabelResponse -> ShowS
Prelude.Show, forall x.
Rep CreateReturnShippingLabelResponse x
-> CreateReturnShippingLabelResponse
forall x.
CreateReturnShippingLabelResponse
-> Rep CreateReturnShippingLabelResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateReturnShippingLabelResponse x
-> CreateReturnShippingLabelResponse
$cfrom :: forall x.
CreateReturnShippingLabelResponse
-> Rep CreateReturnShippingLabelResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateReturnShippingLabelResponse' 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:
--
-- 'status', 'createReturnShippingLabelResponse_status' - The status information of the task on a Snow device that is being
-- returned to Amazon Web Services.
--
-- 'httpStatus', 'createReturnShippingLabelResponse_httpStatus' - The response's http status code.
newCreateReturnShippingLabelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateReturnShippingLabelResponse
newCreateReturnShippingLabelResponse :: Int -> CreateReturnShippingLabelResponse
newCreateReturnShippingLabelResponse Int
pHttpStatus_ =
  CreateReturnShippingLabelResponse'
    { $sel:status:CreateReturnShippingLabelResponse' :: Maybe ShippingLabelStatus
status =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateReturnShippingLabelResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The status information of the task on a Snow device that is being
-- returned to Amazon Web Services.
createReturnShippingLabelResponse_status :: Lens.Lens' CreateReturnShippingLabelResponse (Prelude.Maybe ShippingLabelStatus)
createReturnShippingLabelResponse_status :: Lens' CreateReturnShippingLabelResponse (Maybe ShippingLabelStatus)
createReturnShippingLabelResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateReturnShippingLabelResponse' {Maybe ShippingLabelStatus
status :: Maybe ShippingLabelStatus
$sel:status:CreateReturnShippingLabelResponse' :: CreateReturnShippingLabelResponse -> Maybe ShippingLabelStatus
status} -> Maybe ShippingLabelStatus
status) (\s :: CreateReturnShippingLabelResponse
s@CreateReturnShippingLabelResponse' {} Maybe ShippingLabelStatus
a -> CreateReturnShippingLabelResponse
s {$sel:status:CreateReturnShippingLabelResponse' :: Maybe ShippingLabelStatus
status = Maybe ShippingLabelStatus
a} :: CreateReturnShippingLabelResponse)

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

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