{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}
module Data.Geospatial.Internal.Geometry.GeoPoint (
GeoPoint(..)
, unGeoPoint
, retrieveXY
) where
import Control.DeepSeq
import Control.Lens (makeLenses)
import Control.Monad (mzero)
import qualified Data.Aeson as Aeson
import Data.Geospatial.Internal.BasicTypes
import Data.Geospatial.Internal.Geometry.Aeson
import GHC.Generics (Generic)
newtype GeoPoint = GeoPoint { GeoPoint -> GeoPositionWithoutCRS
_unGeoPoint :: GeoPositionWithoutCRS } deriving (Int -> GeoPoint -> ShowS
[GeoPoint] -> ShowS
GeoPoint -> String
(Int -> GeoPoint -> ShowS)
-> (GeoPoint -> String) -> ([GeoPoint] -> ShowS) -> Show GeoPoint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GeoPoint] -> ShowS
$cshowList :: [GeoPoint] -> ShowS
show :: GeoPoint -> String
$cshow :: GeoPoint -> String
showsPrec :: Int -> GeoPoint -> ShowS
$cshowsPrec :: Int -> GeoPoint -> ShowS
Show, GeoPoint -> GeoPoint -> Bool
(GeoPoint -> GeoPoint -> Bool)
-> (GeoPoint -> GeoPoint -> Bool) -> Eq GeoPoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GeoPoint -> GeoPoint -> Bool
$c/= :: GeoPoint -> GeoPoint -> Bool
== :: GeoPoint -> GeoPoint -> Bool
$c== :: GeoPoint -> GeoPoint -> Bool
Eq, (forall x. GeoPoint -> Rep GeoPoint x)
-> (forall x. Rep GeoPoint x -> GeoPoint) -> Generic GeoPoint
forall x. Rep GeoPoint x -> GeoPoint
forall x. GeoPoint -> Rep GeoPoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GeoPoint x -> GeoPoint
$cfrom :: forall x. GeoPoint -> Rep GeoPoint x
Generic, GeoPoint -> ()
(GeoPoint -> ()) -> NFData GeoPoint
forall a. (a -> ()) -> NFData a
rnf :: GeoPoint -> ()
$crnf :: GeoPoint -> ()
NFData)
makeLenses ''GeoPoint
instance Aeson.ToJSON GeoPoint where
toJSON :: GeoPoint -> Value
toJSON = String -> GeoPositionWithoutCRS -> Value
forall a. ToJSON a => String -> a -> Value
makeGeometryGeoAeson String
"Point" (GeoPositionWithoutCRS -> Value)
-> (GeoPoint -> GeoPositionWithoutCRS) -> GeoPoint -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GeoPoint -> GeoPositionWithoutCRS
_unGeoPoint
instance Aeson.FromJSON GeoPoint where
parseJSON :: Value -> Parser GeoPoint
parseJSON (Aeson.Object Object
o) = String
-> (GeoPositionWithoutCRS -> GeoPoint) -> Object -> Parser GeoPoint
forall a b.
(FromJSON a, FromJSON b) =>
String -> (a -> b) -> Object -> Parser b
readGeometryGeoAeson String
"Point" GeoPositionWithoutCRS -> GeoPoint
GeoPoint Object
o
parseJSON Value
_ = Parser GeoPoint
forall (m :: * -> *) a. MonadPlus m => m a
mzero