{-# 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.GetMapSprites
-- 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 sprite sheet corresponding to a map resource. The sprite
-- sheet is a PNG image paired with a JSON document describing the offsets
-- of individual icons that will be displayed on a rendered map.
module Amazonka.Location.GetMapSprites
  ( -- * Creating a Request
    GetMapSprites (..),
    newGetMapSprites,

    -- * Request Lenses
    getMapSprites_fileName,
    getMapSprites_mapName,

    -- * Destructuring the Response
    GetMapSpritesResponse (..),
    newGetMapSpritesResponse,

    -- * Response Lenses
    getMapSpritesResponse_blob,
    getMapSpritesResponse_contentType,
    getMapSpritesResponse_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:/ 'newGetMapSprites' smart constructor.
data GetMapSprites = GetMapSprites'
  { -- | The name of the sprite file. Use the following file names for the sprite
    -- sheet:
    --
    -- -   @sprites.png@
    --
    -- -   @sprites\@2x.png@ for high pixel density displays
    --
    -- For the JSON document containing image offsets. Use the following file
    -- names:
    --
    -- -   @sprites.json@
    --
    -- -   @sprites\@2x.json@ for high pixel density displays
    GetMapSprites -> Text
fileName :: Prelude.Text,
    -- | The map resource associated with the sprite file.
    GetMapSprites -> Text
mapName :: Prelude.Text
  }
  deriving (GetMapSprites -> GetMapSprites -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMapSprites -> GetMapSprites -> Bool
$c/= :: GetMapSprites -> GetMapSprites -> Bool
== :: GetMapSprites -> GetMapSprites -> Bool
$c== :: GetMapSprites -> GetMapSprites -> Bool
Prelude.Eq, ReadPrec [GetMapSprites]
ReadPrec GetMapSprites
Int -> ReadS GetMapSprites
ReadS [GetMapSprites]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMapSprites]
$creadListPrec :: ReadPrec [GetMapSprites]
readPrec :: ReadPrec GetMapSprites
$creadPrec :: ReadPrec GetMapSprites
readList :: ReadS [GetMapSprites]
$creadList :: ReadS [GetMapSprites]
readsPrec :: Int -> ReadS GetMapSprites
$creadsPrec :: Int -> ReadS GetMapSprites
Prelude.Read, Int -> GetMapSprites -> ShowS
[GetMapSprites] -> ShowS
GetMapSprites -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMapSprites] -> ShowS
$cshowList :: [GetMapSprites] -> ShowS
show :: GetMapSprites -> String
$cshow :: GetMapSprites -> String
showsPrec :: Int -> GetMapSprites -> ShowS
$cshowsPrec :: Int -> GetMapSprites -> ShowS
Prelude.Show, forall x. Rep GetMapSprites x -> GetMapSprites
forall x. GetMapSprites -> Rep GetMapSprites x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMapSprites x -> GetMapSprites
$cfrom :: forall x. GetMapSprites -> Rep GetMapSprites x
Prelude.Generic)

-- |
-- Create a value of 'GetMapSprites' 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:
--
-- 'fileName', 'getMapSprites_fileName' - The name of the sprite file. Use the following file names for the sprite
-- sheet:
--
-- -   @sprites.png@
--
-- -   @sprites\@2x.png@ for high pixel density displays
--
-- For the JSON document containing image offsets. Use the following file
-- names:
--
-- -   @sprites.json@
--
-- -   @sprites\@2x.json@ for high pixel density displays
--
-- 'mapName', 'getMapSprites_mapName' - The map resource associated with the sprite file.
newGetMapSprites ::
  -- | 'fileName'
  Prelude.Text ->
  -- | 'mapName'
  Prelude.Text ->
  GetMapSprites
newGetMapSprites :: Text -> Text -> GetMapSprites
newGetMapSprites Text
pFileName_ Text
pMapName_ =
  GetMapSprites'
    { $sel:fileName:GetMapSprites' :: Text
fileName = Text
pFileName_,
      $sel:mapName:GetMapSprites' :: Text
mapName = Text
pMapName_
    }

-- | The name of the sprite file. Use the following file names for the sprite
-- sheet:
--
-- -   @sprites.png@
--
-- -   @sprites\@2x.png@ for high pixel density displays
--
-- For the JSON document containing image offsets. Use the following file
-- names:
--
-- -   @sprites.json@
--
-- -   @sprites\@2x.json@ for high pixel density displays
getMapSprites_fileName :: Lens.Lens' GetMapSprites Prelude.Text
getMapSprites_fileName :: Lens' GetMapSprites Text
getMapSprites_fileName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMapSprites' {Text
fileName :: Text
$sel:fileName:GetMapSprites' :: GetMapSprites -> Text
fileName} -> Text
fileName) (\s :: GetMapSprites
s@GetMapSprites' {} Text
a -> GetMapSprites
s {$sel:fileName:GetMapSprites' :: Text
fileName = Text
a} :: GetMapSprites)

-- | The map resource associated with the sprite file.
getMapSprites_mapName :: Lens.Lens' GetMapSprites Prelude.Text
getMapSprites_mapName :: Lens' GetMapSprites Text
getMapSprites_mapName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMapSprites' {Text
mapName :: Text
$sel:mapName:GetMapSprites' :: GetMapSprites -> Text
mapName} -> Text
mapName) (\s :: GetMapSprites
s@GetMapSprites' {} Text
a -> GetMapSprites
s {$sel:mapName:GetMapSprites' :: Text
mapName = Text
a} :: GetMapSprites)

instance Core.AWSRequest GetMapSprites where
  type
    AWSResponse GetMapSprites =
      GetMapSpritesResponse
  request :: (Service -> Service) -> GetMapSprites -> Request GetMapSprites
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 GetMapSprites
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetMapSprites)))
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 -> GetMapSpritesResponse
GetMapSpritesResponse'
            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 GetMapSprites where
  hashWithSalt :: Int -> GetMapSprites -> Int
hashWithSalt Int
_salt GetMapSprites' {Text
mapName :: Text
fileName :: Text
$sel:mapName:GetMapSprites' :: GetMapSprites -> Text
$sel:fileName:GetMapSprites' :: GetMapSprites -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fileName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
mapName

instance Prelude.NFData GetMapSprites where
  rnf :: GetMapSprites -> ()
rnf GetMapSprites' {Text
mapName :: Text
fileName :: Text
$sel:mapName:GetMapSprites' :: GetMapSprites -> Text
$sel:fileName:GetMapSprites' :: GetMapSprites -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
fileName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
mapName

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

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

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

-- |
-- Create a value of 'GetMapSpritesResponse' 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', 'getMapSpritesResponse_blob' - Contains the body of the sprite sheet or JSON offset file.
--
-- 'contentType', 'getMapSpritesResponse_contentType' - The content type of the sprite sheet and offsets. For example, the
-- sprite sheet content type is @image\/png@, and the sprite offset JSON
-- document is @application\/json@.
--
-- 'httpStatus', 'getMapSpritesResponse_httpStatus' - The response's http status code.
newGetMapSpritesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetMapSpritesResponse
newGetMapSpritesResponse :: Int -> GetMapSpritesResponse
newGetMapSpritesResponse Int
pHttpStatus_ =
  GetMapSpritesResponse'
    { $sel:blob:GetMapSpritesResponse' :: Maybe ByteString
blob = forall a. Maybe a
Prelude.Nothing,
      $sel:contentType:GetMapSpritesResponse' :: Maybe Text
contentType = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetMapSpritesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Contains the body of the sprite sheet or JSON offset file.
getMapSpritesResponse_blob :: Lens.Lens' GetMapSpritesResponse (Prelude.Maybe Prelude.ByteString)
getMapSpritesResponse_blob :: Lens' GetMapSpritesResponse (Maybe ByteString)
getMapSpritesResponse_blob = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMapSpritesResponse' {Maybe ByteString
blob :: Maybe ByteString
$sel:blob:GetMapSpritesResponse' :: GetMapSpritesResponse -> Maybe ByteString
blob} -> Maybe ByteString
blob) (\s :: GetMapSpritesResponse
s@GetMapSpritesResponse' {} Maybe ByteString
a -> GetMapSpritesResponse
s {$sel:blob:GetMapSpritesResponse' :: Maybe ByteString
blob = Maybe ByteString
a} :: GetMapSpritesResponse)

-- | The content type of the sprite sheet and offsets. For example, the
-- sprite sheet content type is @image\/png@, and the sprite offset JSON
-- document is @application\/json@.
getMapSpritesResponse_contentType :: Lens.Lens' GetMapSpritesResponse (Prelude.Maybe Prelude.Text)
getMapSpritesResponse_contentType :: Lens' GetMapSpritesResponse (Maybe Text)
getMapSpritesResponse_contentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMapSpritesResponse' {Maybe Text
contentType :: Maybe Text
$sel:contentType:GetMapSpritesResponse' :: GetMapSpritesResponse -> Maybe Text
contentType} -> Maybe Text
contentType) (\s :: GetMapSpritesResponse
s@GetMapSpritesResponse' {} Maybe Text
a -> GetMapSpritesResponse
s {$sel:contentType:GetMapSpritesResponse' :: Maybe Text
contentType = Maybe Text
a} :: GetMapSpritesResponse)

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

instance Prelude.NFData GetMapSpritesResponse where
  rnf :: GetMapSpritesResponse -> ()
rnf GetMapSpritesResponse' {Int
Maybe ByteString
Maybe Text
httpStatus :: Int
contentType :: Maybe Text
blob :: Maybe ByteString
$sel:httpStatus:GetMapSpritesResponse' :: GetMapSpritesResponse -> Int
$sel:contentType:GetMapSpritesResponse' :: GetMapSpritesResponse -> Maybe Text
$sel:blob:GetMapSpritesResponse' :: GetMapSpritesResponse -> 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