{-# 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.IoT1ClickProjects.CreatePlacement
-- 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 empty placement.
module Amazonka.IoT1ClickProjects.CreatePlacement
  ( -- * Creating a Request
    CreatePlacement (..),
    newCreatePlacement,

    -- * Request Lenses
    createPlacement_attributes,
    createPlacement_placementName,
    createPlacement_projectName,

    -- * Destructuring the Response
    CreatePlacementResponse (..),
    newCreatePlacementResponse,

    -- * Response Lenses
    createPlacementResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreatePlacement' smart constructor.
data CreatePlacement = CreatePlacement'
  { -- | Optional user-defined key\/value pairs providing contextual data (such
    -- as location or function) for the placement.
    CreatePlacement -> Maybe (HashMap Text Text)
attributes :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the placement to be created.
    CreatePlacement -> Text
placementName :: Prelude.Text,
    -- | The name of the project in which to create the placement.
    CreatePlacement -> Text
projectName :: Prelude.Text
  }
  deriving (CreatePlacement -> CreatePlacement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePlacement -> CreatePlacement -> Bool
$c/= :: CreatePlacement -> CreatePlacement -> Bool
== :: CreatePlacement -> CreatePlacement -> Bool
$c== :: CreatePlacement -> CreatePlacement -> Bool
Prelude.Eq, ReadPrec [CreatePlacement]
ReadPrec CreatePlacement
Int -> ReadS CreatePlacement
ReadS [CreatePlacement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePlacement]
$creadListPrec :: ReadPrec [CreatePlacement]
readPrec :: ReadPrec CreatePlacement
$creadPrec :: ReadPrec CreatePlacement
readList :: ReadS [CreatePlacement]
$creadList :: ReadS [CreatePlacement]
readsPrec :: Int -> ReadS CreatePlacement
$creadsPrec :: Int -> ReadS CreatePlacement
Prelude.Read, Int -> CreatePlacement -> ShowS
[CreatePlacement] -> ShowS
CreatePlacement -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePlacement] -> ShowS
$cshowList :: [CreatePlacement] -> ShowS
show :: CreatePlacement -> String
$cshow :: CreatePlacement -> String
showsPrec :: Int -> CreatePlacement -> ShowS
$cshowsPrec :: Int -> CreatePlacement -> ShowS
Prelude.Show, forall x. Rep CreatePlacement x -> CreatePlacement
forall x. CreatePlacement -> Rep CreatePlacement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreatePlacement x -> CreatePlacement
$cfrom :: forall x. CreatePlacement -> Rep CreatePlacement x
Prelude.Generic)

-- |
-- Create a value of 'CreatePlacement' 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:
--
-- 'attributes', 'createPlacement_attributes' - Optional user-defined key\/value pairs providing contextual data (such
-- as location or function) for the placement.
--
-- 'placementName', 'createPlacement_placementName' - The name of the placement to be created.
--
-- 'projectName', 'createPlacement_projectName' - The name of the project in which to create the placement.
newCreatePlacement ::
  -- | 'placementName'
  Prelude.Text ->
  -- | 'projectName'
  Prelude.Text ->
  CreatePlacement
newCreatePlacement :: Text -> Text -> CreatePlacement
newCreatePlacement Text
pPlacementName_ Text
pProjectName_ =
  CreatePlacement'
    { $sel:attributes:CreatePlacement' :: Maybe (HashMap Text Text)
attributes = forall a. Maybe a
Prelude.Nothing,
      $sel:placementName:CreatePlacement' :: Text
placementName = Text
pPlacementName_,
      $sel:projectName:CreatePlacement' :: Text
projectName = Text
pProjectName_
    }

-- | Optional user-defined key\/value pairs providing contextual data (such
-- as location or function) for the placement.
createPlacement_attributes :: Lens.Lens' CreatePlacement (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createPlacement_attributes :: Lens' CreatePlacement (Maybe (HashMap Text Text))
createPlacement_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePlacement' {Maybe (HashMap Text Text)
attributes :: Maybe (HashMap Text Text)
$sel:attributes:CreatePlacement' :: CreatePlacement -> Maybe (HashMap Text Text)
attributes} -> Maybe (HashMap Text Text)
attributes) (\s :: CreatePlacement
s@CreatePlacement' {} Maybe (HashMap Text Text)
a -> CreatePlacement
s {$sel:attributes:CreatePlacement' :: Maybe (HashMap Text Text)
attributes = Maybe (HashMap Text Text)
a} :: CreatePlacement) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The name of the placement to be created.
createPlacement_placementName :: Lens.Lens' CreatePlacement Prelude.Text
createPlacement_placementName :: Lens' CreatePlacement Text
createPlacement_placementName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePlacement' {Text
placementName :: Text
$sel:placementName:CreatePlacement' :: CreatePlacement -> Text
placementName} -> Text
placementName) (\s :: CreatePlacement
s@CreatePlacement' {} Text
a -> CreatePlacement
s {$sel:placementName:CreatePlacement' :: Text
placementName = Text
a} :: CreatePlacement)

-- | The name of the project in which to create the placement.
createPlacement_projectName :: Lens.Lens' CreatePlacement Prelude.Text
createPlacement_projectName :: Lens' CreatePlacement Text
createPlacement_projectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePlacement' {Text
projectName :: Text
$sel:projectName:CreatePlacement' :: CreatePlacement -> Text
projectName} -> Text
projectName) (\s :: CreatePlacement
s@CreatePlacement' {} Text
a -> CreatePlacement
s {$sel:projectName:CreatePlacement' :: Text
projectName = Text
a} :: CreatePlacement)

instance Core.AWSRequest CreatePlacement where
  type
    AWSResponse CreatePlacement =
      CreatePlacementResponse
  request :: (Service -> Service) -> CreatePlacement -> Request CreatePlacement
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 CreatePlacement
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreatePlacement)))
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 -> CreatePlacementResponse
CreatePlacementResponse'
            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 CreatePlacement where
  hashWithSalt :: Int -> CreatePlacement -> Int
hashWithSalt Int
_salt CreatePlacement' {Maybe (HashMap Text Text)
Text
projectName :: Text
placementName :: Text
attributes :: Maybe (HashMap Text Text)
$sel:projectName:CreatePlacement' :: CreatePlacement -> Text
$sel:placementName:CreatePlacement' :: CreatePlacement -> Text
$sel:attributes:CreatePlacement' :: CreatePlacement -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
attributes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
placementName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectName

instance Prelude.NFData CreatePlacement where
  rnf :: CreatePlacement -> ()
rnf CreatePlacement' {Maybe (HashMap Text Text)
Text
projectName :: Text
placementName :: Text
attributes :: Maybe (HashMap Text Text)
$sel:projectName:CreatePlacement' :: CreatePlacement -> Text
$sel:placementName:CreatePlacement' :: CreatePlacement -> Text
$sel:attributes:CreatePlacement' :: CreatePlacement -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
attributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
placementName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
projectName

instance Data.ToHeaders CreatePlacement where
  toHeaders :: CreatePlacement -> 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 CreatePlacement where
  toJSON :: CreatePlacement -> Value
toJSON CreatePlacement' {Maybe (HashMap Text Text)
Text
projectName :: Text
placementName :: Text
attributes :: Maybe (HashMap Text Text)
$sel:projectName:CreatePlacement' :: CreatePlacement -> Text
$sel:placementName:CreatePlacement' :: CreatePlacement -> Text
$sel:attributes:CreatePlacement' :: CreatePlacement -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"attributes" 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 (HashMap Text Text)
attributes,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"placementName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
placementName)
          ]
      )

instance Data.ToPath CreatePlacement where
  toPath :: CreatePlacement -> ByteString
toPath CreatePlacement' {Maybe (HashMap Text Text)
Text
projectName :: Text
placementName :: Text
attributes :: Maybe (HashMap Text Text)
$sel:projectName:CreatePlacement' :: CreatePlacement -> Text
$sel:placementName:CreatePlacement' :: CreatePlacement -> Text
$sel:attributes:CreatePlacement' :: CreatePlacement -> Maybe (HashMap Text Text)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/projects/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
projectName, ByteString
"/placements"]

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

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

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

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

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