{-# 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.GetMapStyleDescriptor
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the map style descriptor from a map resource.
--
-- The style descriptor contains specifications on how features render on a
-- map. For example, what data to display, what order to display the data
-- in, and the style for the data. Style descriptors follow the Mapbox
-- Style Specification.
module Amazonka.Location.GetMapStyleDescriptor
  ( -- * Creating a Request
    GetMapStyleDescriptor (..),
    newGetMapStyleDescriptor,

    -- * Request Lenses
    getMapStyleDescriptor_mapName,

    -- * Destructuring the Response
    GetMapStyleDescriptorResponse (..),
    newGetMapStyleDescriptorResponse,

    -- * Response Lenses
    getMapStyleDescriptorResponse_blob,
    getMapStyleDescriptorResponse_contentType,
    getMapStyleDescriptorResponse_httpStatus,
  )
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:/ 'newGetMapStyleDescriptor' smart constructor.
data GetMapStyleDescriptor = GetMapStyleDescriptor'
  { -- | The map resource to retrieve the style descriptor from.
    GetMapStyleDescriptor -> Text
mapName :: Prelude.Text
  }
  deriving (GetMapStyleDescriptor -> GetMapStyleDescriptor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMapStyleDescriptor -> GetMapStyleDescriptor -> Bool
$c/= :: GetMapStyleDescriptor -> GetMapStyleDescriptor -> Bool
== :: GetMapStyleDescriptor -> GetMapStyleDescriptor -> Bool
$c== :: GetMapStyleDescriptor -> GetMapStyleDescriptor -> Bool
Prelude.Eq, ReadPrec [GetMapStyleDescriptor]
ReadPrec GetMapStyleDescriptor
Int -> ReadS GetMapStyleDescriptor
ReadS [GetMapStyleDescriptor]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMapStyleDescriptor]
$creadListPrec :: ReadPrec [GetMapStyleDescriptor]
readPrec :: ReadPrec GetMapStyleDescriptor
$creadPrec :: ReadPrec GetMapStyleDescriptor
readList :: ReadS [GetMapStyleDescriptor]
$creadList :: ReadS [GetMapStyleDescriptor]
readsPrec :: Int -> ReadS GetMapStyleDescriptor
$creadsPrec :: Int -> ReadS GetMapStyleDescriptor
Prelude.Read, Int -> GetMapStyleDescriptor -> ShowS
[GetMapStyleDescriptor] -> ShowS
GetMapStyleDescriptor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMapStyleDescriptor] -> ShowS
$cshowList :: [GetMapStyleDescriptor] -> ShowS
show :: GetMapStyleDescriptor -> String
$cshow :: GetMapStyleDescriptor -> String
showsPrec :: Int -> GetMapStyleDescriptor -> ShowS
$cshowsPrec :: Int -> GetMapStyleDescriptor -> ShowS
Prelude.Show, forall x. Rep GetMapStyleDescriptor x -> GetMapStyleDescriptor
forall x. GetMapStyleDescriptor -> Rep GetMapStyleDescriptor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMapStyleDescriptor x -> GetMapStyleDescriptor
$cfrom :: forall x. GetMapStyleDescriptor -> Rep GetMapStyleDescriptor x
Prelude.Generic)

-- |
-- Create a value of 'GetMapStyleDescriptor' 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:
--
-- 'mapName', 'getMapStyleDescriptor_mapName' - The map resource to retrieve the style descriptor from.
newGetMapStyleDescriptor ::
  -- | 'mapName'
  Prelude.Text ->
  GetMapStyleDescriptor
newGetMapStyleDescriptor :: Text -> GetMapStyleDescriptor
newGetMapStyleDescriptor Text
pMapName_ =
  GetMapStyleDescriptor' {$sel:mapName:GetMapStyleDescriptor' :: Text
mapName = Text
pMapName_}

-- | The map resource to retrieve the style descriptor from.
getMapStyleDescriptor_mapName :: Lens.Lens' GetMapStyleDescriptor Prelude.Text
getMapStyleDescriptor_mapName :: Lens' GetMapStyleDescriptor Text
getMapStyleDescriptor_mapName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMapStyleDescriptor' {Text
mapName :: Text
$sel:mapName:GetMapStyleDescriptor' :: GetMapStyleDescriptor -> Text
mapName} -> Text
mapName) (\s :: GetMapStyleDescriptor
s@GetMapStyleDescriptor' {} Text
a -> GetMapStyleDescriptor
s {$sel:mapName:GetMapStyleDescriptor' :: Text
mapName = Text
a} :: GetMapStyleDescriptor)

instance Core.AWSRequest GetMapStyleDescriptor where
  type
    AWSResponse GetMapStyleDescriptor =
      GetMapStyleDescriptorResponse
  request :: (Service -> Service)
-> GetMapStyleDescriptor -> Request GetMapStyleDescriptor
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetMapStyleDescriptor
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetMapStyleDescriptor)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int
 -> ResponseHeaders -> ByteString -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveBytes
      ( \Int
s ResponseHeaders
h ByteString
x ->
          Maybe ByteString
-> Maybe Text -> Int -> GetMapStyleDescriptorResponse
GetMapStyleDescriptorResponse'
            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. a -> Maybe a
Prelude.Just (coerce :: forall a b. Coercible a b => a -> b
Prelude.coerce ByteString
x)))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Content-Type")
            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 GetMapStyleDescriptor where
  hashWithSalt :: Int -> GetMapStyleDescriptor -> Int
hashWithSalt Int
_salt GetMapStyleDescriptor' {Text
mapName :: Text
$sel:mapName:GetMapStyleDescriptor' :: GetMapStyleDescriptor -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
mapName

instance Prelude.NFData GetMapStyleDescriptor where
  rnf :: GetMapStyleDescriptor -> ()
rnf GetMapStyleDescriptor' {Text
mapName :: Text
$sel:mapName:GetMapStyleDescriptor' :: GetMapStyleDescriptor -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
mapName

instance Data.ToHeaders GetMapStyleDescriptor where
  toHeaders :: GetMapStyleDescriptor -> 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.ToPath GetMapStyleDescriptor where
  toPath :: GetMapStyleDescriptor -> ByteString
toPath GetMapStyleDescriptor' {Text
mapName :: Text
$sel:mapName:GetMapStyleDescriptor' :: GetMapStyleDescriptor -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/maps/v0/maps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
mapName,
        ByteString
"/style-descriptor"
      ]

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

-- | /See:/ 'newGetMapStyleDescriptorResponse' smart constructor.
data GetMapStyleDescriptorResponse = GetMapStyleDescriptorResponse'
  { -- | Contains the body of the style descriptor.
    GetMapStyleDescriptorResponse -> Maybe ByteString
blob :: Prelude.Maybe Prelude.ByteString,
    -- | The style descriptor\'s content type. For example, @application\/json@.
    GetMapStyleDescriptorResponse -> Maybe Text
contentType :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetMapStyleDescriptorResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetMapStyleDescriptorResponse
-> GetMapStyleDescriptorResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMapStyleDescriptorResponse
-> GetMapStyleDescriptorResponse -> Bool
$c/= :: GetMapStyleDescriptorResponse
-> GetMapStyleDescriptorResponse -> Bool
== :: GetMapStyleDescriptorResponse
-> GetMapStyleDescriptorResponse -> Bool
$c== :: GetMapStyleDescriptorResponse
-> GetMapStyleDescriptorResponse -> Bool
Prelude.Eq, ReadPrec [GetMapStyleDescriptorResponse]
ReadPrec GetMapStyleDescriptorResponse
Int -> ReadS GetMapStyleDescriptorResponse
ReadS [GetMapStyleDescriptorResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMapStyleDescriptorResponse]
$creadListPrec :: ReadPrec [GetMapStyleDescriptorResponse]
readPrec :: ReadPrec GetMapStyleDescriptorResponse
$creadPrec :: ReadPrec GetMapStyleDescriptorResponse
readList :: ReadS [GetMapStyleDescriptorResponse]
$creadList :: ReadS [GetMapStyleDescriptorResponse]
readsPrec :: Int -> ReadS GetMapStyleDescriptorResponse
$creadsPrec :: Int -> ReadS GetMapStyleDescriptorResponse
Prelude.Read, Int -> GetMapStyleDescriptorResponse -> ShowS
[GetMapStyleDescriptorResponse] -> ShowS
GetMapStyleDescriptorResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMapStyleDescriptorResponse] -> ShowS
$cshowList :: [GetMapStyleDescriptorResponse] -> ShowS
show :: GetMapStyleDescriptorResponse -> String
$cshow :: GetMapStyleDescriptorResponse -> String
showsPrec :: Int -> GetMapStyleDescriptorResponse -> ShowS
$cshowsPrec :: Int -> GetMapStyleDescriptorResponse -> ShowS
Prelude.Show, forall x.
Rep GetMapStyleDescriptorResponse x
-> GetMapStyleDescriptorResponse
forall x.
GetMapStyleDescriptorResponse
-> Rep GetMapStyleDescriptorResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetMapStyleDescriptorResponse x
-> GetMapStyleDescriptorResponse
$cfrom :: forall x.
GetMapStyleDescriptorResponse
-> Rep GetMapStyleDescriptorResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetMapStyleDescriptorResponse' 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:
--
-- 'blob', 'getMapStyleDescriptorResponse_blob' - Contains the body of the style descriptor.
--
-- 'contentType', 'getMapStyleDescriptorResponse_contentType' - The style descriptor\'s content type. For example, @application\/json@.
--
-- 'httpStatus', 'getMapStyleDescriptorResponse_httpStatus' - The response's http status code.
newGetMapStyleDescriptorResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetMapStyleDescriptorResponse
newGetMapStyleDescriptorResponse :: Int -> GetMapStyleDescriptorResponse
newGetMapStyleDescriptorResponse Int
pHttpStatus_ =
  GetMapStyleDescriptorResponse'
    { $sel:blob:GetMapStyleDescriptorResponse' :: Maybe ByteString
blob =
        forall a. Maybe a
Prelude.Nothing,
      $sel:contentType:GetMapStyleDescriptorResponse' :: Maybe Text
contentType = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetMapStyleDescriptorResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Contains the body of the style descriptor.
getMapStyleDescriptorResponse_blob :: Lens.Lens' GetMapStyleDescriptorResponse (Prelude.Maybe Prelude.ByteString)
getMapStyleDescriptorResponse_blob :: Lens' GetMapStyleDescriptorResponse (Maybe ByteString)
getMapStyleDescriptorResponse_blob = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMapStyleDescriptorResponse' {Maybe ByteString
blob :: Maybe ByteString
$sel:blob:GetMapStyleDescriptorResponse' :: GetMapStyleDescriptorResponse -> Maybe ByteString
blob} -> Maybe ByteString
blob) (\s :: GetMapStyleDescriptorResponse
s@GetMapStyleDescriptorResponse' {} Maybe ByteString
a -> GetMapStyleDescriptorResponse
s {$sel:blob:GetMapStyleDescriptorResponse' :: Maybe ByteString
blob = Maybe ByteString
a} :: GetMapStyleDescriptorResponse)

-- | The style descriptor\'s content type. For example, @application\/json@.
getMapStyleDescriptorResponse_contentType :: Lens.Lens' GetMapStyleDescriptorResponse (Prelude.Maybe Prelude.Text)
getMapStyleDescriptorResponse_contentType :: Lens' GetMapStyleDescriptorResponse (Maybe Text)
getMapStyleDescriptorResponse_contentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMapStyleDescriptorResponse' {Maybe Text
contentType :: Maybe Text
$sel:contentType:GetMapStyleDescriptorResponse' :: GetMapStyleDescriptorResponse -> Maybe Text
contentType} -> Maybe Text
contentType) (\s :: GetMapStyleDescriptorResponse
s@GetMapStyleDescriptorResponse' {} Maybe Text
a -> GetMapStyleDescriptorResponse
s {$sel:contentType:GetMapStyleDescriptorResponse' :: Maybe Text
contentType = Maybe Text
a} :: GetMapStyleDescriptorResponse)

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

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