{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.SearchForPositionResult
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Location.Types.SearchForPositionResult 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.Place
import qualified Amazonka.Prelude as Prelude

-- | Contains a search result from a position search query that is run on a
-- place index resource.
--
-- /See:/ 'newSearchForPositionResult' smart constructor.
data SearchForPositionResult = SearchForPositionResult'
  { -- | The unique identifier of the place. You can use this with the @GetPlace@
    -- operation to find the place again later.
    --
    -- For @SearchPlaceIndexForPosition@ operations, the @PlaceId@ is returned
    -- only by place indexes that use HERE as a data provider.
    SearchForPositionResult -> Maybe Text
placeId :: Prelude.Maybe Prelude.Text,
    -- | The distance in meters of a great-circle arc between the query position
    -- and the result.
    --
    -- A great-circle arc is the shortest path on a sphere, in this case the
    -- Earth. This returns the shortest distance between two locations.
    SearchForPositionResult -> Double
distance :: Prelude.Double,
    -- | Details about the search result, such as its address and position.
    SearchForPositionResult -> Place
place :: Place
  }
  deriving (SearchForPositionResult -> SearchForPositionResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchForPositionResult -> SearchForPositionResult -> Bool
$c/= :: SearchForPositionResult -> SearchForPositionResult -> Bool
== :: SearchForPositionResult -> SearchForPositionResult -> Bool
$c== :: SearchForPositionResult -> SearchForPositionResult -> Bool
Prelude.Eq, Int -> SearchForPositionResult -> ShowS
[SearchForPositionResult] -> ShowS
SearchForPositionResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchForPositionResult] -> ShowS
$cshowList :: [SearchForPositionResult] -> ShowS
show :: SearchForPositionResult -> String
$cshow :: SearchForPositionResult -> String
showsPrec :: Int -> SearchForPositionResult -> ShowS
$cshowsPrec :: Int -> SearchForPositionResult -> ShowS
Prelude.Show, forall x. Rep SearchForPositionResult x -> SearchForPositionResult
forall x. SearchForPositionResult -> Rep SearchForPositionResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchForPositionResult x -> SearchForPositionResult
$cfrom :: forall x. SearchForPositionResult -> Rep SearchForPositionResult x
Prelude.Generic)

-- |
-- Create a value of 'SearchForPositionResult' 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:
--
-- 'placeId', 'searchForPositionResult_placeId' - The unique identifier of the place. You can use this with the @GetPlace@
-- operation to find the place again later.
--
-- For @SearchPlaceIndexForPosition@ operations, the @PlaceId@ is returned
-- only by place indexes that use HERE as a data provider.
--
-- 'distance', 'searchForPositionResult_distance' - The distance in meters of a great-circle arc between the query position
-- and the result.
--
-- A great-circle arc is the shortest path on a sphere, in this case the
-- Earth. This returns the shortest distance between two locations.
--
-- 'place', 'searchForPositionResult_place' - Details about the search result, such as its address and position.
newSearchForPositionResult ::
  -- | 'distance'
  Prelude.Double ->
  -- | 'place'
  Place ->
  SearchForPositionResult
newSearchForPositionResult :: Double -> Place -> SearchForPositionResult
newSearchForPositionResult Double
pDistance_ Place
pPlace_ =
  SearchForPositionResult'
    { $sel:placeId:SearchForPositionResult' :: Maybe Text
placeId = forall a. Maybe a
Prelude.Nothing,
      $sel:distance:SearchForPositionResult' :: Double
distance = Double
pDistance_,
      $sel:place:SearchForPositionResult' :: Place
place = Place
pPlace_
    }

-- | The unique identifier of the place. You can use this with the @GetPlace@
-- operation to find the place again later.
--
-- For @SearchPlaceIndexForPosition@ operations, the @PlaceId@ is returned
-- only by place indexes that use HERE as a data provider.
searchForPositionResult_placeId :: Lens.Lens' SearchForPositionResult (Prelude.Maybe Prelude.Text)
searchForPositionResult_placeId :: Lens' SearchForPositionResult (Maybe Text)
searchForPositionResult_placeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchForPositionResult' {Maybe Text
placeId :: Maybe Text
$sel:placeId:SearchForPositionResult' :: SearchForPositionResult -> Maybe Text
placeId} -> Maybe Text
placeId) (\s :: SearchForPositionResult
s@SearchForPositionResult' {} Maybe Text
a -> SearchForPositionResult
s {$sel:placeId:SearchForPositionResult' :: Maybe Text
placeId = Maybe Text
a} :: SearchForPositionResult)

-- | The distance in meters of a great-circle arc between the query position
-- and the result.
--
-- A great-circle arc is the shortest path on a sphere, in this case the
-- Earth. This returns the shortest distance between two locations.
searchForPositionResult_distance :: Lens.Lens' SearchForPositionResult Prelude.Double
searchForPositionResult_distance :: Lens' SearchForPositionResult Double
searchForPositionResult_distance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchForPositionResult' {Double
distance :: Double
$sel:distance:SearchForPositionResult' :: SearchForPositionResult -> Double
distance} -> Double
distance) (\s :: SearchForPositionResult
s@SearchForPositionResult' {} Double
a -> SearchForPositionResult
s {$sel:distance:SearchForPositionResult' :: Double
distance = Double
a} :: SearchForPositionResult)

-- | Details about the search result, such as its address and position.
searchForPositionResult_place :: Lens.Lens' SearchForPositionResult Place
searchForPositionResult_place :: Lens' SearchForPositionResult Place
searchForPositionResult_place = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchForPositionResult' {Place
place :: Place
$sel:place:SearchForPositionResult' :: SearchForPositionResult -> Place
place} -> Place
place) (\s :: SearchForPositionResult
s@SearchForPositionResult' {} Place
a -> SearchForPositionResult
s {$sel:place:SearchForPositionResult' :: Place
place = Place
a} :: SearchForPositionResult)

instance Data.FromJSON SearchForPositionResult where
  parseJSON :: Value -> Parser SearchForPositionResult
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SearchForPositionResult"
      ( \Object
x ->
          Maybe Text -> Double -> Place -> SearchForPositionResult
SearchForPositionResult'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"PlaceId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Distance")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Place")
      )

instance Prelude.Hashable SearchForPositionResult where
  hashWithSalt :: Int -> SearchForPositionResult -> Int
hashWithSalt Int
_salt SearchForPositionResult' {Double
Maybe Text
Place
place :: Place
distance :: Double
placeId :: Maybe Text
$sel:place:SearchForPositionResult' :: SearchForPositionResult -> Place
$sel:distance:SearchForPositionResult' :: SearchForPositionResult -> Double
$sel:placeId:SearchForPositionResult' :: SearchForPositionResult -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
placeId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Double
distance
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Place
place

instance Prelude.NFData SearchForPositionResult where
  rnf :: SearchForPositionResult -> ()
rnf SearchForPositionResult' {Double
Maybe Text
Place
place :: Place
distance :: Double
placeId :: Maybe Text
$sel:place:SearchForPositionResult' :: SearchForPositionResult -> Place
$sel:distance:SearchForPositionResult' :: SearchForPositionResult -> Double
$sel:placeId:SearchForPositionResult' :: SearchForPositionResult -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
placeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Double
distance
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Place
place