{-# 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.IoTWireless.StartFuotaTask
-- 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 a FUOTA task.
module Amazonka.IoTWireless.StartFuotaTask
  ( -- * Creating a Request
    StartFuotaTask (..),
    newStartFuotaTask,

    -- * Request Lenses
    startFuotaTask_loRaWAN,
    startFuotaTask_id,

    -- * Destructuring the Response
    StartFuotaTaskResponse (..),
    newStartFuotaTaskResponse,

    -- * Response Lenses
    startFuotaTaskResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStartFuotaTask' smart constructor.
data StartFuotaTask = StartFuotaTask'
  { StartFuotaTask -> Maybe LoRaWANStartFuotaTask
loRaWAN :: Prelude.Maybe LoRaWANStartFuotaTask,
    StartFuotaTask -> Text
id :: Prelude.Text
  }
  deriving (StartFuotaTask -> StartFuotaTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartFuotaTask -> StartFuotaTask -> Bool
$c/= :: StartFuotaTask -> StartFuotaTask -> Bool
== :: StartFuotaTask -> StartFuotaTask -> Bool
$c== :: StartFuotaTask -> StartFuotaTask -> Bool
Prelude.Eq, ReadPrec [StartFuotaTask]
ReadPrec StartFuotaTask
Int -> ReadS StartFuotaTask
ReadS [StartFuotaTask]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartFuotaTask]
$creadListPrec :: ReadPrec [StartFuotaTask]
readPrec :: ReadPrec StartFuotaTask
$creadPrec :: ReadPrec StartFuotaTask
readList :: ReadS [StartFuotaTask]
$creadList :: ReadS [StartFuotaTask]
readsPrec :: Int -> ReadS StartFuotaTask
$creadsPrec :: Int -> ReadS StartFuotaTask
Prelude.Read, Int -> StartFuotaTask -> ShowS
[StartFuotaTask] -> ShowS
StartFuotaTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartFuotaTask] -> ShowS
$cshowList :: [StartFuotaTask] -> ShowS
show :: StartFuotaTask -> String
$cshow :: StartFuotaTask -> String
showsPrec :: Int -> StartFuotaTask -> ShowS
$cshowsPrec :: Int -> StartFuotaTask -> ShowS
Prelude.Show, forall x. Rep StartFuotaTask x -> StartFuotaTask
forall x. StartFuotaTask -> Rep StartFuotaTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartFuotaTask x -> StartFuotaTask
$cfrom :: forall x. StartFuotaTask -> Rep StartFuotaTask x
Prelude.Generic)

-- |
-- Create a value of 'StartFuotaTask' 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:
--
-- 'loRaWAN', 'startFuotaTask_loRaWAN' - Undocumented member.
--
-- 'id', 'startFuotaTask_id' - Undocumented member.
newStartFuotaTask ::
  -- | 'id'
  Prelude.Text ->
  StartFuotaTask
newStartFuotaTask :: Text -> StartFuotaTask
newStartFuotaTask Text
pId_ =
  StartFuotaTask'
    { $sel:loRaWAN:StartFuotaTask' :: Maybe LoRaWANStartFuotaTask
loRaWAN = forall a. Maybe a
Prelude.Nothing,
      $sel:id:StartFuotaTask' :: Text
id = Text
pId_
    }

-- | Undocumented member.
startFuotaTask_loRaWAN :: Lens.Lens' StartFuotaTask (Prelude.Maybe LoRaWANStartFuotaTask)
startFuotaTask_loRaWAN :: Lens' StartFuotaTask (Maybe LoRaWANStartFuotaTask)
startFuotaTask_loRaWAN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFuotaTask' {Maybe LoRaWANStartFuotaTask
loRaWAN :: Maybe LoRaWANStartFuotaTask
$sel:loRaWAN:StartFuotaTask' :: StartFuotaTask -> Maybe LoRaWANStartFuotaTask
loRaWAN} -> Maybe LoRaWANStartFuotaTask
loRaWAN) (\s :: StartFuotaTask
s@StartFuotaTask' {} Maybe LoRaWANStartFuotaTask
a -> StartFuotaTask
s {$sel:loRaWAN:StartFuotaTask' :: Maybe LoRaWANStartFuotaTask
loRaWAN = Maybe LoRaWANStartFuotaTask
a} :: StartFuotaTask)

-- | Undocumented member.
startFuotaTask_id :: Lens.Lens' StartFuotaTask Prelude.Text
startFuotaTask_id :: Lens' StartFuotaTask Text
startFuotaTask_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartFuotaTask' {Text
id :: Text
$sel:id:StartFuotaTask' :: StartFuotaTask -> Text
id} -> Text
id) (\s :: StartFuotaTask
s@StartFuotaTask' {} Text
a -> StartFuotaTask
s {$sel:id:StartFuotaTask' :: Text
id = Text
a} :: StartFuotaTask)

instance Core.AWSRequest StartFuotaTask where
  type
    AWSResponse StartFuotaTask =
      StartFuotaTaskResponse
  request :: (Service -> Service) -> StartFuotaTask -> Request StartFuotaTask
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy StartFuotaTask
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartFuotaTask)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> StartFuotaTaskResponse
StartFuotaTaskResponse'
            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))
      )

instance Prelude.Hashable StartFuotaTask where
  hashWithSalt :: Int -> StartFuotaTask -> Int
hashWithSalt Int
_salt StartFuotaTask' {Maybe LoRaWANStartFuotaTask
Text
id :: Text
loRaWAN :: Maybe LoRaWANStartFuotaTask
$sel:id:StartFuotaTask' :: StartFuotaTask -> Text
$sel:loRaWAN:StartFuotaTask' :: StartFuotaTask -> Maybe LoRaWANStartFuotaTask
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LoRaWANStartFuotaTask
loRaWAN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData StartFuotaTask where
  rnf :: StartFuotaTask -> ()
rnf StartFuotaTask' {Maybe LoRaWANStartFuotaTask
Text
id :: Text
loRaWAN :: Maybe LoRaWANStartFuotaTask
$sel:id:StartFuotaTask' :: StartFuotaTask -> Text
$sel:loRaWAN:StartFuotaTask' :: StartFuotaTask -> Maybe LoRaWANStartFuotaTask
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe LoRaWANStartFuotaTask
loRaWAN seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

instance Data.ToHeaders StartFuotaTask where
  toHeaders :: StartFuotaTask -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON StartFuotaTask where
  toJSON :: StartFuotaTask -> Value
toJSON StartFuotaTask' {Maybe LoRaWANStartFuotaTask
Text
id :: Text
loRaWAN :: Maybe LoRaWANStartFuotaTask
$sel:id:StartFuotaTask' :: StartFuotaTask -> Text
$sel:loRaWAN:StartFuotaTask' :: StartFuotaTask -> Maybe LoRaWANStartFuotaTask
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"LoRaWAN" 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 LoRaWANStartFuotaTask
loRaWAN]
      )

instance Data.ToPath StartFuotaTask where
  toPath :: StartFuotaTask -> ByteString
toPath StartFuotaTask' {Maybe LoRaWANStartFuotaTask
Text
id :: Text
loRaWAN :: Maybe LoRaWANStartFuotaTask
$sel:id:StartFuotaTask' :: StartFuotaTask -> Text
$sel:loRaWAN:StartFuotaTask' :: StartFuotaTask -> Maybe LoRaWANStartFuotaTask
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/fuota-tasks/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

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

-- |
-- Create a value of 'StartFuotaTaskResponse' 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', 'startFuotaTaskResponse_httpStatus' - The response's http status code.
newStartFuotaTaskResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartFuotaTaskResponse
newStartFuotaTaskResponse :: Int -> StartFuotaTaskResponse
newStartFuotaTaskResponse Int
pHttpStatus_ =
  StartFuotaTaskResponse' {$sel:httpStatus:StartFuotaTaskResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData StartFuotaTaskResponse where
  rnf :: StartFuotaTaskResponse -> ()
rnf StartFuotaTaskResponse' {Int
httpStatus :: Int
$sel:httpStatus:StartFuotaTaskResponse' :: StartFuotaTaskResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus