{-# 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.Location.UpdateMap
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the specified properties of a given map resource.
module Amazonka.Location.UpdateMap
  ( -- * Creating a Request
    UpdateMap (..),
    newUpdateMap,

    -- * Request Lenses
    updateMap_description,
    updateMap_pricingPlan,
    updateMap_mapName,

    -- * Destructuring the Response
    UpdateMapResponse (..),
    newUpdateMapResponse,

    -- * Response Lenses
    updateMapResponse_httpStatus,
    updateMapResponse_mapArn,
    updateMapResponse_mapName,
    updateMapResponse_updateTime,
  )
where

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

-- | /See:/ 'newUpdateMap' smart constructor.
data UpdateMap = UpdateMap'
  { -- | Updates the description for the map resource.
    UpdateMap -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | No longer used. If included, the only allowed value is
    -- @RequestBasedUsage@.
    UpdateMap -> Maybe PricingPlan
pricingPlan :: Prelude.Maybe PricingPlan,
    -- | The name of the map resource to update.
    UpdateMap -> Text
mapName :: Prelude.Text
  }
  deriving (UpdateMap -> UpdateMap -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateMap -> UpdateMap -> Bool
$c/= :: UpdateMap -> UpdateMap -> Bool
== :: UpdateMap -> UpdateMap -> Bool
$c== :: UpdateMap -> UpdateMap -> Bool
Prelude.Eq, ReadPrec [UpdateMap]
ReadPrec UpdateMap
Int -> ReadS UpdateMap
ReadS [UpdateMap]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateMap]
$creadListPrec :: ReadPrec [UpdateMap]
readPrec :: ReadPrec UpdateMap
$creadPrec :: ReadPrec UpdateMap
readList :: ReadS [UpdateMap]
$creadList :: ReadS [UpdateMap]
readsPrec :: Int -> ReadS UpdateMap
$creadsPrec :: Int -> ReadS UpdateMap
Prelude.Read, Int -> UpdateMap -> ShowS
[UpdateMap] -> ShowS
UpdateMap -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateMap] -> ShowS
$cshowList :: [UpdateMap] -> ShowS
show :: UpdateMap -> String
$cshow :: UpdateMap -> String
showsPrec :: Int -> UpdateMap -> ShowS
$cshowsPrec :: Int -> UpdateMap -> ShowS
Prelude.Show, forall x. Rep UpdateMap x -> UpdateMap
forall x. UpdateMap -> Rep UpdateMap x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateMap x -> UpdateMap
$cfrom :: forall x. UpdateMap -> Rep UpdateMap x
Prelude.Generic)

-- |
-- Create a value of 'UpdateMap' 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:
--
-- 'description', 'updateMap_description' - Updates the description for the map resource.
--
-- 'pricingPlan', 'updateMap_pricingPlan' - No longer used. If included, the only allowed value is
-- @RequestBasedUsage@.
--
-- 'mapName', 'updateMap_mapName' - The name of the map resource to update.
newUpdateMap ::
  -- | 'mapName'
  Prelude.Text ->
  UpdateMap
newUpdateMap :: Text -> UpdateMap
newUpdateMap Text
pMapName_ =
  UpdateMap'
    { $sel:description:UpdateMap' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:pricingPlan:UpdateMap' :: Maybe PricingPlan
pricingPlan = forall a. Maybe a
Prelude.Nothing,
      $sel:mapName:UpdateMap' :: Text
mapName = Text
pMapName_
    }

-- | Updates the description for the map resource.
updateMap_description :: Lens.Lens' UpdateMap (Prelude.Maybe Prelude.Text)
updateMap_description :: Lens' UpdateMap (Maybe Text)
updateMap_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMap' {Maybe Text
description :: Maybe Text
$sel:description:UpdateMap' :: UpdateMap -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateMap
s@UpdateMap' {} Maybe Text
a -> UpdateMap
s {$sel:description:UpdateMap' :: Maybe Text
description = Maybe Text
a} :: UpdateMap)

-- | No longer used. If included, the only allowed value is
-- @RequestBasedUsage@.
updateMap_pricingPlan :: Lens.Lens' UpdateMap (Prelude.Maybe PricingPlan)
updateMap_pricingPlan :: Lens' UpdateMap (Maybe PricingPlan)
updateMap_pricingPlan = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMap' {Maybe PricingPlan
pricingPlan :: Maybe PricingPlan
$sel:pricingPlan:UpdateMap' :: UpdateMap -> Maybe PricingPlan
pricingPlan} -> Maybe PricingPlan
pricingPlan) (\s :: UpdateMap
s@UpdateMap' {} Maybe PricingPlan
a -> UpdateMap
s {$sel:pricingPlan:UpdateMap' :: Maybe PricingPlan
pricingPlan = Maybe PricingPlan
a} :: UpdateMap)

-- | The name of the map resource to update.
updateMap_mapName :: Lens.Lens' UpdateMap Prelude.Text
updateMap_mapName :: Lens' UpdateMap Text
updateMap_mapName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMap' {Text
mapName :: Text
$sel:mapName:UpdateMap' :: UpdateMap -> Text
mapName} -> Text
mapName) (\s :: UpdateMap
s@UpdateMap' {} Text
a -> UpdateMap
s {$sel:mapName:UpdateMap' :: Text
mapName = Text
a} :: UpdateMap)

instance Core.AWSRequest UpdateMap where
  type AWSResponse UpdateMap = UpdateMapResponse
  request :: (Service -> Service) -> UpdateMap -> Request UpdateMap
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateMap
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateMap)))
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 ->
          Int -> Text -> Text -> ISO8601 -> UpdateMapResponse
UpdateMapResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"MapArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"MapName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"UpdateTime")
      )

instance Prelude.Hashable UpdateMap where
  hashWithSalt :: Int -> UpdateMap -> Int
hashWithSalt Int
_salt UpdateMap' {Maybe Text
Maybe PricingPlan
Text
mapName :: Text
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
$sel:mapName:UpdateMap' :: UpdateMap -> Text
$sel:pricingPlan:UpdateMap' :: UpdateMap -> Maybe PricingPlan
$sel:description:UpdateMap' :: UpdateMap -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PricingPlan
pricingPlan
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
mapName

instance Prelude.NFData UpdateMap where
  rnf :: UpdateMap -> ()
rnf UpdateMap' {Maybe Text
Maybe PricingPlan
Text
mapName :: Text
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
$sel:mapName:UpdateMap' :: UpdateMap -> Text
$sel:pricingPlan:UpdateMap' :: UpdateMap -> Maybe PricingPlan
$sel:description:UpdateMap' :: UpdateMap -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PricingPlan
pricingPlan
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
mapName

instance Data.ToHeaders UpdateMap where
  toHeaders :: UpdateMap -> 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 UpdateMap where
  toJSON :: UpdateMap -> Value
toJSON UpdateMap' {Maybe Text
Maybe PricingPlan
Text
mapName :: Text
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
$sel:mapName:UpdateMap' :: UpdateMap -> Text
$sel:pricingPlan:UpdateMap' :: UpdateMap -> Maybe PricingPlan
$sel:description:UpdateMap' :: UpdateMap -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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 Text
description,
            (Key
"PricingPlan" 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 PricingPlan
pricingPlan
          ]
      )

instance Data.ToPath UpdateMap where
  toPath :: UpdateMap -> ByteString
toPath UpdateMap' {Maybe Text
Maybe PricingPlan
Text
mapName :: Text
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
$sel:mapName:UpdateMap' :: UpdateMap -> Text
$sel:pricingPlan:UpdateMap' :: UpdateMap -> Maybe PricingPlan
$sel:description:UpdateMap' :: UpdateMap -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/maps/v0/maps/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
mapName]

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

-- | /See:/ 'newUpdateMapResponse' smart constructor.
data UpdateMapResponse = UpdateMapResponse'
  { -- | The response's http status code.
    UpdateMapResponse -> Int
httpStatus :: Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the updated map resource. Used to
    -- specify a resource across AWS.
    --
    -- -   Format example: @arn:aws:geo:region:account-id:map\/ExampleMap@
    UpdateMapResponse -> Text
mapArn :: Prelude.Text,
    -- | The name of the updated map resource.
    UpdateMapResponse -> Text
mapName :: Prelude.Text,
    -- | The timestamp for when the map resource was last updated in
    -- <https://www.iso.org/iso-8601-date-and-time-format.html ISO 8601>
    -- format: @YYYY-MM-DDThh:mm:ss.sssZ@.
    UpdateMapResponse -> ISO8601
updateTime :: Data.ISO8601
  }
  deriving (UpdateMapResponse -> UpdateMapResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateMapResponse -> UpdateMapResponse -> Bool
$c/= :: UpdateMapResponse -> UpdateMapResponse -> Bool
== :: UpdateMapResponse -> UpdateMapResponse -> Bool
$c== :: UpdateMapResponse -> UpdateMapResponse -> Bool
Prelude.Eq, ReadPrec [UpdateMapResponse]
ReadPrec UpdateMapResponse
Int -> ReadS UpdateMapResponse
ReadS [UpdateMapResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateMapResponse]
$creadListPrec :: ReadPrec [UpdateMapResponse]
readPrec :: ReadPrec UpdateMapResponse
$creadPrec :: ReadPrec UpdateMapResponse
readList :: ReadS [UpdateMapResponse]
$creadList :: ReadS [UpdateMapResponse]
readsPrec :: Int -> ReadS UpdateMapResponse
$creadsPrec :: Int -> ReadS UpdateMapResponse
Prelude.Read, Int -> UpdateMapResponse -> ShowS
[UpdateMapResponse] -> ShowS
UpdateMapResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateMapResponse] -> ShowS
$cshowList :: [UpdateMapResponse] -> ShowS
show :: UpdateMapResponse -> String
$cshow :: UpdateMapResponse -> String
showsPrec :: Int -> UpdateMapResponse -> ShowS
$cshowsPrec :: Int -> UpdateMapResponse -> ShowS
Prelude.Show, forall x. Rep UpdateMapResponse x -> UpdateMapResponse
forall x. UpdateMapResponse -> Rep UpdateMapResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateMapResponse x -> UpdateMapResponse
$cfrom :: forall x. UpdateMapResponse -> Rep UpdateMapResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateMapResponse' 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', 'updateMapResponse_httpStatus' - The response's http status code.
--
-- 'mapArn', 'updateMapResponse_mapArn' - The Amazon Resource Name (ARN) of the updated map resource. Used to
-- specify a resource across AWS.
--
-- -   Format example: @arn:aws:geo:region:account-id:map\/ExampleMap@
--
-- 'mapName', 'updateMapResponse_mapName' - The name of the updated map resource.
--
-- 'updateTime', 'updateMapResponse_updateTime' - The timestamp for when the map resource was last updated in
-- <https://www.iso.org/iso-8601-date-and-time-format.html ISO 8601>
-- format: @YYYY-MM-DDThh:mm:ss.sssZ@.
newUpdateMapResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'mapArn'
  Prelude.Text ->
  -- | 'mapName'
  Prelude.Text ->
  -- | 'updateTime'
  Prelude.UTCTime ->
  UpdateMapResponse
newUpdateMapResponse :: Int -> Text -> Text -> UTCTime -> UpdateMapResponse
newUpdateMapResponse
  Int
pHttpStatus_
  Text
pMapArn_
  Text
pMapName_
  UTCTime
pUpdateTime_ =
    UpdateMapResponse'
      { $sel:httpStatus:UpdateMapResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:mapArn:UpdateMapResponse' :: Text
mapArn = Text
pMapArn_,
        $sel:mapName:UpdateMapResponse' :: Text
mapName = Text
pMapName_,
        $sel:updateTime:UpdateMapResponse' :: ISO8601
updateTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pUpdateTime_
      }

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

-- | The Amazon Resource Name (ARN) of the updated map resource. Used to
-- specify a resource across AWS.
--
-- -   Format example: @arn:aws:geo:region:account-id:map\/ExampleMap@
updateMapResponse_mapArn :: Lens.Lens' UpdateMapResponse Prelude.Text
updateMapResponse_mapArn :: Lens' UpdateMapResponse Text
updateMapResponse_mapArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMapResponse' {Text
mapArn :: Text
$sel:mapArn:UpdateMapResponse' :: UpdateMapResponse -> Text
mapArn} -> Text
mapArn) (\s :: UpdateMapResponse
s@UpdateMapResponse' {} Text
a -> UpdateMapResponse
s {$sel:mapArn:UpdateMapResponse' :: Text
mapArn = Text
a} :: UpdateMapResponse)

-- | The name of the updated map resource.
updateMapResponse_mapName :: Lens.Lens' UpdateMapResponse Prelude.Text
updateMapResponse_mapName :: Lens' UpdateMapResponse Text
updateMapResponse_mapName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMapResponse' {Text
mapName :: Text
$sel:mapName:UpdateMapResponse' :: UpdateMapResponse -> Text
mapName} -> Text
mapName) (\s :: UpdateMapResponse
s@UpdateMapResponse' {} Text
a -> UpdateMapResponse
s {$sel:mapName:UpdateMapResponse' :: Text
mapName = Text
a} :: UpdateMapResponse)

-- | The timestamp for when the map resource was last updated in
-- <https://www.iso.org/iso-8601-date-and-time-format.html ISO 8601>
-- format: @YYYY-MM-DDThh:mm:ss.sssZ@.
updateMapResponse_updateTime :: Lens.Lens' UpdateMapResponse Prelude.UTCTime
updateMapResponse_updateTime :: Lens' UpdateMapResponse UTCTime
updateMapResponse_updateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateMapResponse' {ISO8601
updateTime :: ISO8601
$sel:updateTime:UpdateMapResponse' :: UpdateMapResponse -> ISO8601
updateTime} -> ISO8601
updateTime) (\s :: UpdateMapResponse
s@UpdateMapResponse' {} ISO8601
a -> UpdateMapResponse
s {$sel:updateTime:UpdateMapResponse' :: ISO8601
updateTime = ISO8601
a} :: UpdateMapResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.NFData UpdateMapResponse where
  rnf :: UpdateMapResponse -> ()
rnf UpdateMapResponse' {Int
Text
ISO8601
updateTime :: ISO8601
mapName :: Text
mapArn :: Text
httpStatus :: Int
$sel:updateTime:UpdateMapResponse' :: UpdateMapResponse -> ISO8601
$sel:mapName:UpdateMapResponse' :: UpdateMapResponse -> Text
$sel:mapArn:UpdateMapResponse' :: UpdateMapResponse -> Text
$sel:httpStatus:UpdateMapResponse' :: UpdateMapResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
mapArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
mapName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ISO8601
updateTime