{-# LANGUAGE OverloadedStrings #-}
module Data.Geospatial.Internal.BasicTypes (
Latitude
, Longitude
, Easting
, Northing
, Altitude
, GeoPositionWithoutCRS
, Name
, Code
, Href
, FormatString
, ProjectionType
, BoundingBoxWithoutCRS
, FeatureID (..)
) where
import Data.Aeson (FromJSON (..), ToJSON (..), Value (..))
import Data.Scientific (Scientific, toBoundedInteger)
import Data.Text (Text)
type Latitude = Double
type Longitude = Double
type Easting = Double
type Northing = Double
type Altitude = Double
type GeoPositionWithoutCRS = [Double]
type Name = Text
type Code = Int
type Href = Text
type FormatString = Text
type ProjectionType = Text
data FeatureID =
FeatureIDText Text
| FeatureIDNumber Int deriving (Show, Eq)
instance FromJSON FeatureID where
parseJSON (Number nID) =
case x of
Nothing -> fail "Not an integer value"
Just z -> pure $ FeatureIDNumber z
where
x = toBoundedInteger nID :: Maybe Int
parseJSON (String sID) = pure $ FeatureIDText sID
parseJSON _ = fail "unknown id type"
instance ToJSON FeatureID where
toJSON (FeatureIDText a) = String a
toJSON (FeatureIDNumber b) = Number (fromInteger $ toInteger b :: Scientific)
type BoundingBoxWithoutCRS = [Double]