{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Data.Geospatial.Internal.BasicTypes (
Latitude
, Longitude
, Easting
, Northing
, Altitude
, GeoPositionWithoutCRS (..)
, retrieveXY
, PointXY (..)
, PointXYZ (..)
, PointXYZM (..)
, DoubleArray (..)
, HasGeoPositionWithoutCRS(..)
, Name
, Code
, Href
, FormatString
, ProjectionType
, BoundingBoxWithoutCRS (..)
, FeatureID (..)
) where
import Control.DeepSeq
import Control.Lens.TH (makeClassy)
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Types as AesonTypes
import qualified Data.Maybe as DataMaybe
import qualified Data.Scientific as Scientific
import qualified Data.Text as Text
import qualified Data.Vector as Vector
import GHC.Generics
type Latitude = Double
type Longitude = Double
type Easting = Double
type Northing = Double
type Altitude = Double
newtype DoubleArray = DoubleArray [Double] deriving (DoubleArray -> DoubleArray -> Bool
(DoubleArray -> DoubleArray -> Bool)
-> (DoubleArray -> DoubleArray -> Bool) -> Eq DoubleArray
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DoubleArray -> DoubleArray -> Bool
$c/= :: DoubleArray -> DoubleArray -> Bool
== :: DoubleArray -> DoubleArray -> Bool
$c== :: DoubleArray -> DoubleArray -> Bool
Eq, Int -> DoubleArray -> ShowS
[DoubleArray] -> ShowS
DoubleArray -> String
(Int -> DoubleArray -> ShowS)
-> (DoubleArray -> String)
-> ([DoubleArray] -> ShowS)
-> Show DoubleArray
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DoubleArray] -> ShowS
$cshowList :: [DoubleArray] -> ShowS
show :: DoubleArray -> String
$cshow :: DoubleArray -> String
showsPrec :: Int -> DoubleArray -> ShowS
$cshowsPrec :: Int -> DoubleArray -> ShowS
Show, (forall x. DoubleArray -> Rep DoubleArray x)
-> (forall x. Rep DoubleArray x -> DoubleArray)
-> Generic DoubleArray
forall x. Rep DoubleArray x -> DoubleArray
forall x. DoubleArray -> Rep DoubleArray x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DoubleArray x -> DoubleArray
$cfrom :: forall x. DoubleArray -> Rep DoubleArray x
Generic, DoubleArray -> ()
(DoubleArray -> ()) -> NFData DoubleArray
forall a. (a -> ()) -> NFData a
rnf :: DoubleArray -> ()
$crnf :: DoubleArray -> ()
NFData, Value -> Parser [DoubleArray]
Value -> Parser DoubleArray
(Value -> Parser DoubleArray)
-> (Value -> Parser [DoubleArray]) -> FromJSON DoubleArray
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DoubleArray]
$cparseJSONList :: Value -> Parser [DoubleArray]
parseJSON :: Value -> Parser DoubleArray
$cparseJSON :: Value -> Parser DoubleArray
Aeson.FromJSON, [DoubleArray] -> Encoding
[DoubleArray] -> Value
DoubleArray -> Encoding
DoubleArray -> Value
(DoubleArray -> Value)
-> (DoubleArray -> Encoding)
-> ([DoubleArray] -> Value)
-> ([DoubleArray] -> Encoding)
-> ToJSON DoubleArray
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DoubleArray] -> Encoding
$ctoEncodingList :: [DoubleArray] -> Encoding
toJSONList :: [DoubleArray] -> Value
$ctoJSONList :: [DoubleArray] -> Value
toEncoding :: DoubleArray -> Encoding
$ctoEncoding :: DoubleArray -> Encoding
toJSON :: DoubleArray -> Value
$ctoJSON :: DoubleArray -> Value
Aeson.ToJSON)
data PointXY = PointXY
{ PointXY -> Double
_xyX :: !Double
, PointXY -> Double
_xyY :: !Double
} deriving (Int -> PointXY -> ShowS
[PointXY] -> ShowS
PointXY -> String
(Int -> PointXY -> ShowS)
-> (PointXY -> String) -> ([PointXY] -> ShowS) -> Show PointXY
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PointXY] -> ShowS
$cshowList :: [PointXY] -> ShowS
show :: PointXY -> String
$cshow :: PointXY -> String
showsPrec :: Int -> PointXY -> ShowS
$cshowsPrec :: Int -> PointXY -> ShowS
Show, PointXY -> PointXY -> Bool
(PointXY -> PointXY -> Bool)
-> (PointXY -> PointXY -> Bool) -> Eq PointXY
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PointXY -> PointXY -> Bool
$c/= :: PointXY -> PointXY -> Bool
== :: PointXY -> PointXY -> Bool
$c== :: PointXY -> PointXY -> Bool
Eq, (forall x. PointXY -> Rep PointXY x)
-> (forall x. Rep PointXY x -> PointXY) -> Generic PointXY
forall x. Rep PointXY x -> PointXY
forall x. PointXY -> Rep PointXY x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PointXY x -> PointXY
$cfrom :: forall x. PointXY -> Rep PointXY x
Generic, PointXY -> ()
(PointXY -> ()) -> NFData PointXY
forall a. (a -> ()) -> NFData a
rnf :: PointXY -> ()
$crnf :: PointXY -> ()
NFData)
data PointXYZ = PointXYZ
{ PointXYZ -> Double
_xyzX :: !Double
, PointXYZ -> Double
_xyzY :: !Double
, PointXYZ -> Double
_xyzZ :: !Double
} deriving (Int -> PointXYZ -> ShowS
[PointXYZ] -> ShowS
PointXYZ -> String
(Int -> PointXYZ -> ShowS)
-> (PointXYZ -> String) -> ([PointXYZ] -> ShowS) -> Show PointXYZ
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PointXYZ] -> ShowS
$cshowList :: [PointXYZ] -> ShowS
show :: PointXYZ -> String
$cshow :: PointXYZ -> String
showsPrec :: Int -> PointXYZ -> ShowS
$cshowsPrec :: Int -> PointXYZ -> ShowS
Show, PointXYZ -> PointXYZ -> Bool
(PointXYZ -> PointXYZ -> Bool)
-> (PointXYZ -> PointXYZ -> Bool) -> Eq PointXYZ
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PointXYZ -> PointXYZ -> Bool
$c/= :: PointXYZ -> PointXYZ -> Bool
== :: PointXYZ -> PointXYZ -> Bool
$c== :: PointXYZ -> PointXYZ -> Bool
Eq, (forall x. PointXYZ -> Rep PointXYZ x)
-> (forall x. Rep PointXYZ x -> PointXYZ) -> Generic PointXYZ
forall x. Rep PointXYZ x -> PointXYZ
forall x. PointXYZ -> Rep PointXYZ x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PointXYZ x -> PointXYZ
$cfrom :: forall x. PointXYZ -> Rep PointXYZ x
Generic, PointXYZ -> ()
(PointXYZ -> ()) -> NFData PointXYZ
forall a. (a -> ()) -> NFData a
rnf :: PointXYZ -> ()
$crnf :: PointXYZ -> ()
NFData)
data PointXYZM = PointXYZM
{ PointXYZM -> Double
_xyzmX :: !Double
, PointXYZM -> Double
_xyzmY :: !Double
, PointXYZM -> Double
_xyzmZ :: !Double
, PointXYZM -> Double
_xyzmM :: !Double
} deriving (Int -> PointXYZM -> ShowS
[PointXYZM] -> ShowS
PointXYZM -> String
(Int -> PointXYZM -> ShowS)
-> (PointXYZM -> String)
-> ([PointXYZM] -> ShowS)
-> Show PointXYZM
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PointXYZM] -> ShowS
$cshowList :: [PointXYZM] -> ShowS
show :: PointXYZM -> String
$cshow :: PointXYZM -> String
showsPrec :: Int -> PointXYZM -> ShowS
$cshowsPrec :: Int -> PointXYZM -> ShowS
Show, PointXYZM -> PointXYZM -> Bool
(PointXYZM -> PointXYZM -> Bool)
-> (PointXYZM -> PointXYZM -> Bool) -> Eq PointXYZM
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PointXYZM -> PointXYZM -> Bool
$c/= :: PointXYZM -> PointXYZM -> Bool
== :: PointXYZM -> PointXYZM -> Bool
$c== :: PointXYZM -> PointXYZM -> Bool
Eq, (forall x. PointXYZM -> Rep PointXYZM x)
-> (forall x. Rep PointXYZM x -> PointXYZM) -> Generic PointXYZM
forall x. Rep PointXYZM x -> PointXYZM
forall x. PointXYZM -> Rep PointXYZM x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PointXYZM x -> PointXYZM
$cfrom :: forall x. PointXYZM -> Rep PointXYZM x
Generic, PointXYZM -> ()
(PointXYZM -> ()) -> NFData PointXYZM
forall a. (a -> ()) -> NFData a
rnf :: PointXYZM -> ()
$crnf :: PointXYZM -> ()
NFData)
data GeoPositionWithoutCRS = GeoEmpty | GeoPointXY PointXY | GeoPointXYZ PointXYZ | GeoPointXYZM PointXYZM deriving (Int -> GeoPositionWithoutCRS -> ShowS
[GeoPositionWithoutCRS] -> ShowS
GeoPositionWithoutCRS -> String
(Int -> GeoPositionWithoutCRS -> ShowS)
-> (GeoPositionWithoutCRS -> String)
-> ([GeoPositionWithoutCRS] -> ShowS)
-> Show GeoPositionWithoutCRS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GeoPositionWithoutCRS] -> ShowS
$cshowList :: [GeoPositionWithoutCRS] -> ShowS
show :: GeoPositionWithoutCRS -> String
$cshow :: GeoPositionWithoutCRS -> String
showsPrec :: Int -> GeoPositionWithoutCRS -> ShowS
$cshowsPrec :: Int -> GeoPositionWithoutCRS -> ShowS
Show, GeoPositionWithoutCRS -> GeoPositionWithoutCRS -> Bool
(GeoPositionWithoutCRS -> GeoPositionWithoutCRS -> Bool)
-> (GeoPositionWithoutCRS -> GeoPositionWithoutCRS -> Bool)
-> Eq GeoPositionWithoutCRS
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GeoPositionWithoutCRS -> GeoPositionWithoutCRS -> Bool
$c/= :: GeoPositionWithoutCRS -> GeoPositionWithoutCRS -> Bool
== :: GeoPositionWithoutCRS -> GeoPositionWithoutCRS -> Bool
$c== :: GeoPositionWithoutCRS -> GeoPositionWithoutCRS -> Bool
Eq, (forall x. GeoPositionWithoutCRS -> Rep GeoPositionWithoutCRS x)
-> (forall x. Rep GeoPositionWithoutCRS x -> GeoPositionWithoutCRS)
-> Generic GeoPositionWithoutCRS
forall x. Rep GeoPositionWithoutCRS x -> GeoPositionWithoutCRS
forall x. GeoPositionWithoutCRS -> Rep GeoPositionWithoutCRS x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GeoPositionWithoutCRS x -> GeoPositionWithoutCRS
$cfrom :: forall x. GeoPositionWithoutCRS -> Rep GeoPositionWithoutCRS x
Generic, GeoPositionWithoutCRS -> ()
(GeoPositionWithoutCRS -> ()) -> NFData GeoPositionWithoutCRS
forall a. (a -> ()) -> NFData a
rnf :: GeoPositionWithoutCRS -> ()
$crnf :: GeoPositionWithoutCRS -> ()
NFData)
makeClassy ''GeoPositionWithoutCRS
_toDoubleArray :: GeoPositionWithoutCRS -> [Double]
_toDoubleArray :: GeoPositionWithoutCRS -> [Double]
_toDoubleArray GeoPositionWithoutCRS
GeoEmpty = []
_toDoubleArray (GeoPointXY (PointXY Double
x Double
y)) = [Double
x, Double
y]
_toDoubleArray (GeoPointXYZ (PointXYZ Double
x Double
y Double
z)) = [Double
x, Double
y, Double
z]
_toDoubleArray (GeoPointXYZM (PointXYZM Double
x Double
y Double
z Double
m)) = [Double
x, Double
y, Double
z, Double
m]
_toGeoPoint :: DoubleArray -> Maybe GeoPositionWithoutCRS
_toGeoPoint :: DoubleArray -> Maybe GeoPositionWithoutCRS
_toGeoPoint (DoubleArray []) = GeoPositionWithoutCRS -> Maybe GeoPositionWithoutCRS
forall a. a -> Maybe a
Just GeoPositionWithoutCRS
GeoEmpty
_toGeoPoint (DoubleArray [Double
x, Double
y]) = GeoPositionWithoutCRS -> Maybe GeoPositionWithoutCRS
forall a. a -> Maybe a
Just (GeoPositionWithoutCRS -> Maybe GeoPositionWithoutCRS)
-> GeoPositionWithoutCRS -> Maybe GeoPositionWithoutCRS
forall a b. (a -> b) -> a -> b
$ PointXY -> GeoPositionWithoutCRS
GeoPointXY (Double -> Double -> PointXY
PointXY Double
x Double
y)
_toGeoPoint (DoubleArray [Double
x, Double
y, Double
z]) = GeoPositionWithoutCRS -> Maybe GeoPositionWithoutCRS
forall a. a -> Maybe a
Just (GeoPositionWithoutCRS -> Maybe GeoPositionWithoutCRS)
-> GeoPositionWithoutCRS -> Maybe GeoPositionWithoutCRS
forall a b. (a -> b) -> a -> b
$ PointXYZ -> GeoPositionWithoutCRS
GeoPointXYZ (Double -> Double -> Double -> PointXYZ
PointXYZ Double
x Double
y Double
z)
_toGeoPoint (DoubleArray [Double
x, Double
y, Double
z, Double
m]) = GeoPositionWithoutCRS -> Maybe GeoPositionWithoutCRS
forall a. a -> Maybe a
Just (GeoPositionWithoutCRS -> Maybe GeoPositionWithoutCRS)
-> GeoPositionWithoutCRS -> Maybe GeoPositionWithoutCRS
forall a b. (a -> b) -> a -> b
$ PointXYZM -> GeoPositionWithoutCRS
GeoPointXYZM (Double -> Double -> Double -> Double -> PointXYZM
PointXYZM Double
x Double
y Double
z Double
m)
_toGeoPoint DoubleArray
_ = Maybe GeoPositionWithoutCRS
forall a. Maybe a
Nothing
retrieveXY :: GeoPositionWithoutCRS -> PointXY
retrieveXY :: GeoPositionWithoutCRS -> PointXY
retrieveXY GeoPositionWithoutCRS
position =
case GeoPositionWithoutCRS
position of
GeoPositionWithoutCRS
GeoEmpty -> PointXY
forall a. HasCallStack => a
undefined
(GeoPointXY PointXY
p) -> PointXY
p
(GeoPointXYZ (PointXYZ Double
pX Double
pY Double
_)) -> Double -> Double -> PointXY
PointXY Double
pX Double
pY
(GeoPointXYZM (PointXYZM Double
pX Double
pY Double
_ Double
_)) -> Double -> Double -> PointXY
PointXY Double
pX Double
pY
{-# INLINE retrieveXY #-}
instance Aeson.ToJSON GeoPositionWithoutCRS where
toJSON :: GeoPositionWithoutCRS -> Value
toJSON GeoPositionWithoutCRS
a = [Double] -> Value
forall a. ToJSON a => a -> Value
Aeson.toJSON ([Double] -> Value) -> [Double] -> Value
forall a b. (a -> b) -> a -> b
$ GeoPositionWithoutCRS -> [Double]
_toDoubleArray GeoPositionWithoutCRS
a
instance Aeson.FromJSON GeoPositionWithoutCRS where
parseJSON :: Value -> Parser GeoPositionWithoutCRS
parseJSON Value
o = do
DoubleArray
x <- Value -> Parser DoubleArray
forall a. FromJSON a => Value -> Parser a
Aeson.parseJSON Value
o
Parser GeoPositionWithoutCRS
-> (GeoPositionWithoutCRS -> Parser GeoPositionWithoutCRS)
-> Maybe GeoPositionWithoutCRS
-> Parser GeoPositionWithoutCRS
forall b a. b -> (a -> b) -> Maybe a -> b
DataMaybe.maybe (String -> Parser GeoPositionWithoutCRS
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Illegal coordinates") GeoPositionWithoutCRS -> Parser GeoPositionWithoutCRS
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DoubleArray -> Maybe GeoPositionWithoutCRS
_toGeoPoint DoubleArray
x)
type Name = Text.Text
type Code = Int
type Href = Text.Text
type FormatString = Text.Text
type ProjectionType = Text.Text
data FeatureID =
FeatureIDText Text.Text
| FeatureIDNumber Int deriving (Int -> FeatureID -> ShowS
[FeatureID] -> ShowS
FeatureID -> String
(Int -> FeatureID -> ShowS)
-> (FeatureID -> String)
-> ([FeatureID] -> ShowS)
-> Show FeatureID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FeatureID] -> ShowS
$cshowList :: [FeatureID] -> ShowS
show :: FeatureID -> String
$cshow :: FeatureID -> String
showsPrec :: Int -> FeatureID -> ShowS
$cshowsPrec :: Int -> FeatureID -> ShowS
Show, FeatureID -> FeatureID -> Bool
(FeatureID -> FeatureID -> Bool)
-> (FeatureID -> FeatureID -> Bool) -> Eq FeatureID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FeatureID -> FeatureID -> Bool
$c/= :: FeatureID -> FeatureID -> Bool
== :: FeatureID -> FeatureID -> Bool
$c== :: FeatureID -> FeatureID -> Bool
Eq, (forall x. FeatureID -> Rep FeatureID x)
-> (forall x. Rep FeatureID x -> FeatureID) -> Generic FeatureID
forall x. Rep FeatureID x -> FeatureID
forall x. FeatureID -> Rep FeatureID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FeatureID x -> FeatureID
$cfrom :: forall x. FeatureID -> Rep FeatureID x
Generic, FeatureID -> ()
(FeatureID -> ()) -> NFData FeatureID
forall a. (a -> ()) -> NFData a
rnf :: FeatureID -> ()
$crnf :: FeatureID -> ()
NFData)
instance Aeson.FromJSON FeatureID where
parseJSON :: Value -> Parser FeatureID
parseJSON (Aeson.Number Scientific
nID) =
case Maybe Int
x of
Maybe Int
Nothing -> String -> Parser FeatureID
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Not an integer value"
Just Int
z -> FeatureID -> Parser FeatureID
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FeatureID -> Parser FeatureID) -> FeatureID -> Parser FeatureID
forall a b. (a -> b) -> a -> b
$ Int -> FeatureID
FeatureIDNumber Int
z
where
x :: Maybe Int
x = Scientific -> Maybe Int
forall i. (Integral i, Bounded i) => Scientific -> Maybe i
Scientific.toBoundedInteger Scientific
nID :: Maybe Int
parseJSON (Aeson.String Text
sID) = FeatureID -> Parser FeatureID
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FeatureID -> Parser FeatureID) -> FeatureID -> Parser FeatureID
forall a b. (a -> b) -> a -> b
$ Text -> FeatureID
FeatureIDText Text
sID
parseJSON Value
_ = String -> Parser FeatureID
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unknown id type"
instance Aeson.ToJSON FeatureID where
toJSON :: FeatureID -> Value
toJSON (FeatureIDText Text
a) = Text -> Value
Aeson.String Text
a
toJSON (FeatureIDNumber Int
b) = Scientific -> Value
Aeson.Number (Integer -> Scientific
forall a. Num a => Integer -> a
fromInteger (Integer -> Scientific) -> Integer -> Scientific
forall a b. (a -> b) -> a -> b
$ Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
b :: Scientific.Scientific)
data BoundingBoxWithoutCRS
= BoundingBoxWithoutCRSXY PointXY PointXY
| BoundingBoxWithoutCRSXYZ PointXYZ PointXYZ
| BoundingBoxWithoutCRSXYZM PointXYZM PointXYZM deriving (BoundingBoxWithoutCRS -> BoundingBoxWithoutCRS -> Bool
(BoundingBoxWithoutCRS -> BoundingBoxWithoutCRS -> Bool)
-> (BoundingBoxWithoutCRS -> BoundingBoxWithoutCRS -> Bool)
-> Eq BoundingBoxWithoutCRS
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BoundingBoxWithoutCRS -> BoundingBoxWithoutCRS -> Bool
$c/= :: BoundingBoxWithoutCRS -> BoundingBoxWithoutCRS -> Bool
== :: BoundingBoxWithoutCRS -> BoundingBoxWithoutCRS -> Bool
$c== :: BoundingBoxWithoutCRS -> BoundingBoxWithoutCRS -> Bool
Eq, Int -> BoundingBoxWithoutCRS -> ShowS
[BoundingBoxWithoutCRS] -> ShowS
BoundingBoxWithoutCRS -> String
(Int -> BoundingBoxWithoutCRS -> ShowS)
-> (BoundingBoxWithoutCRS -> String)
-> ([BoundingBoxWithoutCRS] -> ShowS)
-> Show BoundingBoxWithoutCRS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BoundingBoxWithoutCRS] -> ShowS
$cshowList :: [BoundingBoxWithoutCRS] -> ShowS
show :: BoundingBoxWithoutCRS -> String
$cshow :: BoundingBoxWithoutCRS -> String
showsPrec :: Int -> BoundingBoxWithoutCRS -> ShowS
$cshowsPrec :: Int -> BoundingBoxWithoutCRS -> ShowS
Show, (forall x. BoundingBoxWithoutCRS -> Rep BoundingBoxWithoutCRS x)
-> (forall x. Rep BoundingBoxWithoutCRS x -> BoundingBoxWithoutCRS)
-> Generic BoundingBoxWithoutCRS
forall x. Rep BoundingBoxWithoutCRS x -> BoundingBoxWithoutCRS
forall x. BoundingBoxWithoutCRS -> Rep BoundingBoxWithoutCRS x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BoundingBoxWithoutCRS x -> BoundingBoxWithoutCRS
$cfrom :: forall x. BoundingBoxWithoutCRS -> Rep BoundingBoxWithoutCRS x
Generic, BoundingBoxWithoutCRS -> ()
(BoundingBoxWithoutCRS -> ()) -> NFData BoundingBoxWithoutCRS
forall a. (a -> ()) -> NFData a
rnf :: BoundingBoxWithoutCRS -> ()
$crnf :: BoundingBoxWithoutCRS -> ()
NFData)
instance Aeson.FromJSON BoundingBoxWithoutCRS where
parseJSON :: Value -> Parser BoundingBoxWithoutCRS
parseJSON Value
json = do
[Double]
x <- Value -> Parser [Double]
forall a. FromJSON a => Value -> Parser a
AesonTypes.parseJSON Value
json
Parser BoundingBoxWithoutCRS
-> (BoundingBoxWithoutCRS -> Parser BoundingBoxWithoutCRS)
-> Maybe BoundingBoxWithoutCRS
-> Parser BoundingBoxWithoutCRS
forall b a. b -> (a -> b) -> Maybe a -> b
DataMaybe.maybe (String -> Parser BoundingBoxWithoutCRS
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid bounding box") BoundingBoxWithoutCRS -> Parser BoundingBoxWithoutCRS
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Double] -> Maybe BoundingBoxWithoutCRS
_toBoundingBoxWithoutCRS [Double]
x)
instance Aeson.ToJSON BoundingBoxWithoutCRS where
toJSON :: BoundingBoxWithoutCRS -> Value
toJSON (BoundingBoxWithoutCRSXY (PointXY Double
bbMinX Double
bbMinY) (PointXY Double
bbMaxX Double
bbMaxY)) =
Array -> Value
Aeson.Array ([Value] -> Array
forall a. [a] -> Vector a
Vector.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ (Double -> Value) -> [Double] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Scientific -> Value
Aeson.Number (Scientific -> Value) -> (Double -> Scientific) -> Double -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Scientific
forall a. RealFloat a => a -> Scientific
Scientific.fromFloatDigits) [Double
bbMinX, Double
bbMinY, Double
bbMaxX, Double
bbMaxY])
toJSON (BoundingBoxWithoutCRSXYZ (PointXYZ Double
bbMinX Double
bbMinY Double
bbMinZ) (PointXYZ Double
bbMaxX Double
bbMaxY Double
bbMaxZ)) =
Array -> Value
Aeson.Array ([Value] -> Array
forall a. [a] -> Vector a
Vector.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ (Double -> Value) -> [Double] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Scientific -> Value
Aeson.Number (Scientific -> Value) -> (Double -> Scientific) -> Double -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Scientific
forall a. RealFloat a => a -> Scientific
Scientific.fromFloatDigits) [Double
bbMinX, Double
bbMinY, Double
bbMinZ, Double
bbMaxX, Double
bbMaxY, Double
bbMaxZ])
toJSON (BoundingBoxWithoutCRSXYZM (PointXYZM Double
bbMinX Double
bbMinY Double
bbMinZ Double
bbMinM) (PointXYZM Double
bbMaxX Double
bbMaxY Double
bbMaxZ Double
bbMaxM)) =
Array -> Value
Aeson.Array ([Value] -> Array
forall a. [a] -> Vector a
Vector.fromList ([Value] -> Array) -> [Value] -> Array
forall a b. (a -> b) -> a -> b
$ (Double -> Value) -> [Double] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Scientific -> Value
Aeson.Number (Scientific -> Value) -> (Double -> Scientific) -> Double -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Scientific
forall a. RealFloat a => a -> Scientific
Scientific.fromFloatDigits) [Double
bbMinX, Double
bbMinY, Double
bbMinZ, Double
bbMinM, Double
bbMaxX, Double
bbMaxY, Double
bbMaxZ, Double
bbMaxM])
_toBoundingBoxWithoutCRS :: [Double] -> Maybe BoundingBoxWithoutCRS
_toBoundingBoxWithoutCRS :: [Double] -> Maybe BoundingBoxWithoutCRS
_toBoundingBoxWithoutCRS [Double
bbMinX, Double
bbMinY, Double
bbMaxX, Double
bbMaxY] =
BoundingBoxWithoutCRS -> Maybe BoundingBoxWithoutCRS
forall a. a -> Maybe a
Just (BoundingBoxWithoutCRS -> Maybe BoundingBoxWithoutCRS)
-> BoundingBoxWithoutCRS -> Maybe BoundingBoxWithoutCRS
forall a b. (a -> b) -> a -> b
$ PointXY -> PointXY -> BoundingBoxWithoutCRS
BoundingBoxWithoutCRSXY (Double -> Double -> PointXY
PointXY Double
bbMinX Double
bbMinY) (Double -> Double -> PointXY
PointXY Double
bbMaxX Double
bbMaxY)
_toBoundingBoxWithoutCRS [Double
bbMinX, Double
bbMinY, Double
bbMinZ, Double
bbMaxX, Double
bbMaxY, Double
bbMaxZ] =
BoundingBoxWithoutCRS -> Maybe BoundingBoxWithoutCRS
forall a. a -> Maybe a
Just (BoundingBoxWithoutCRS -> Maybe BoundingBoxWithoutCRS)
-> BoundingBoxWithoutCRS -> Maybe BoundingBoxWithoutCRS
forall a b. (a -> b) -> a -> b
$ PointXYZ -> PointXYZ -> BoundingBoxWithoutCRS
BoundingBoxWithoutCRSXYZ (Double -> Double -> Double -> PointXYZ
PointXYZ Double
bbMinX Double
bbMinY Double
bbMinZ) (Double -> Double -> Double -> PointXYZ
PointXYZ Double
bbMaxX Double
bbMaxY Double
bbMaxZ)
_toBoundingBoxWithoutCRS [Double
bbMinX, Double
bbMinY, Double
bbMinZ, Double
bbMinM, Double
bbMaxX, Double
bbMaxY, Double
bbMaxZ, Double
bbMaxM] =
BoundingBoxWithoutCRS -> Maybe BoundingBoxWithoutCRS
forall a. a -> Maybe a
Just (BoundingBoxWithoutCRS -> Maybe BoundingBoxWithoutCRS)
-> BoundingBoxWithoutCRS -> Maybe BoundingBoxWithoutCRS
forall a b. (a -> b) -> a -> b
$ PointXYZM -> PointXYZM -> BoundingBoxWithoutCRS
BoundingBoxWithoutCRSXYZM (Double -> Double -> Double -> Double -> PointXYZM
PointXYZM Double
bbMinX Double
bbMinY Double
bbMinZ Double
bbMinM) (Double -> Double -> Double -> Double -> PointXYZM
PointXYZM Double
bbMaxX Double
bbMaxY Double
bbMaxZ Double
bbMaxM)
_toBoundingBoxWithoutCRS [Double]
_ =
Maybe BoundingBoxWithoutCRS
forall a. Maybe a
Nothing