{-# LANGUAGE DeriveGeneric #-}
module Telegram.Bot.API.Types.Location where

import Data.Aeson (FromJSON (..), ToJSON (..))
import GHC.Generics (Generic)

import Telegram.Bot.API.Types.Common
import Telegram.Bot.API.Internal.Utils

-- ** Location

-- | This object represents a point on the map.
data Location = Location
  { Location -> Float
locationLongitude            :: Float         -- ^ Longitude as defined by sender.
  , Location -> Float
locationLatitude             :: Float         -- ^ Latitude as defined by sender.
  , Location -> Maybe Float
locationHorizontalAccuracy   :: Maybe Float   -- ^ The radius of uncertainty for the location, measured in meters; 0-1500.
  , Location -> Maybe Seconds
locationLivePeriod           :: Maybe Seconds -- ^ Time relative to the message sending date, during which the location can be updated; in seconds. For active live locations only.
  , Location -> Maybe Int
locationHeading              :: Maybe Int     -- ^ The direction in which user is moving, in degrees; 1-360. For active live locations only.
  , Location -> Maybe Int
locationProximityAlertRadius :: Maybe Int     -- ^ Maximum distance for proximity alerts about approaching another chat member, in meters. For sent live locations only.
  }
  deriving ((forall x. Location -> Rep Location x)
-> (forall x. Rep Location x -> Location) -> Generic Location
forall x. Rep Location x -> Location
forall x. Location -> Rep Location x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Location -> Rep Location x
from :: forall x. Location -> Rep Location x
$cto :: forall x. Rep Location x -> Location
to :: forall x. Rep Location x -> Location
Generic, Int -> Location -> ShowS
[Location] -> ShowS
Location -> String
(Int -> Location -> ShowS)
-> (Location -> String) -> ([Location] -> ShowS) -> Show Location
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Location -> ShowS
showsPrec :: Int -> Location -> ShowS
$cshow :: Location -> String
show :: Location -> String
$cshowList :: [Location] -> ShowS
showList :: [Location] -> ShowS
Show)

instance ToJSON   Location where toJSON :: Location -> Value
toJSON = Location -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON Location where parseJSON :: Value -> Parser Location
parseJSON = Value -> Parser Location
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON