module Data.Internal.Wkb.Geometry
( GeometryType (..)
, CoordinateType (..)
, WkbGeometryType (..)
, BuilderWkbGeometryType
, getWkbGeom
, builderWkbGeom
, geoPositionWithoutCRSToCoordinateType
, coordTypeOfSequence
, coordTypeOfLinearRings
) where
import qualified Control.Monad as Monad
import qualified Data.Binary.Get as BinaryGet
import qualified Data.ByteString.Builder as ByteStringBuilder
import qualified Data.Geospatial as Geospatial
import qualified Data.LinearRing as LinearRing
import qualified Data.Maybe as Maybe
import qualified Data.Sequence as Sequence
import qualified Data.Word as Word
import qualified Data.Internal.Wkb.Endian as Endian
data GeometryType
= Geometry
| Point
| LineString
| Polygon
| MultiPoint
| MultiLineString
| MultiPolygon
| GeometryCollection deriving (Int -> GeometryType -> ShowS
[GeometryType] -> ShowS
GeometryType -> String
(Int -> GeometryType -> ShowS)
-> (GeometryType -> String)
-> ([GeometryType] -> ShowS)
-> Show GeometryType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GeometryType] -> ShowS
$cshowList :: [GeometryType] -> ShowS
show :: GeometryType -> String
$cshow :: GeometryType -> String
showsPrec :: Int -> GeometryType -> ShowS
$cshowsPrec :: Int -> GeometryType -> ShowS
Show, GeometryType -> GeometryType -> Bool
(GeometryType -> GeometryType -> Bool)
-> (GeometryType -> GeometryType -> Bool) -> Eq GeometryType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GeometryType -> GeometryType -> Bool
$c/= :: GeometryType -> GeometryType -> Bool
== :: GeometryType -> GeometryType -> Bool
$c== :: GeometryType -> GeometryType -> Bool
Eq)
data CoordinateType = TwoD | Z | M | ZM deriving (Int -> CoordinateType -> ShowS
[CoordinateType] -> ShowS
CoordinateType -> String
(Int -> CoordinateType -> ShowS)
-> (CoordinateType -> String)
-> ([CoordinateType] -> ShowS)
-> Show CoordinateType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CoordinateType] -> ShowS
$cshowList :: [CoordinateType] -> ShowS
show :: CoordinateType -> String
$cshow :: CoordinateType -> String
showsPrec :: Int -> CoordinateType -> ShowS
$cshowsPrec :: Int -> CoordinateType -> ShowS
Show, CoordinateType -> CoordinateType -> Bool
(CoordinateType -> CoordinateType -> Bool)
-> (CoordinateType -> CoordinateType -> Bool) -> Eq CoordinateType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CoordinateType -> CoordinateType -> Bool
$c/= :: CoordinateType -> CoordinateType -> Bool
== :: CoordinateType -> CoordinateType -> Bool
$c== :: CoordinateType -> CoordinateType -> Bool
Eq)
data WkbGeometryType = WkbGeom GeometryType CoordinateType deriving (Int -> WkbGeometryType -> ShowS
[WkbGeometryType] -> ShowS
WkbGeometryType -> String
(Int -> WkbGeometryType -> ShowS)
-> (WkbGeometryType -> String)
-> ([WkbGeometryType] -> ShowS)
-> Show WkbGeometryType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WkbGeometryType] -> ShowS
$cshowList :: [WkbGeometryType] -> ShowS
show :: WkbGeometryType -> String
$cshow :: WkbGeometryType -> String
showsPrec :: Int -> WkbGeometryType -> ShowS
$cshowsPrec :: Int -> WkbGeometryType -> ShowS
Show, WkbGeometryType -> WkbGeometryType -> Bool
(WkbGeometryType -> WkbGeometryType -> Bool)
-> (WkbGeometryType -> WkbGeometryType -> Bool)
-> Eq WkbGeometryType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WkbGeometryType -> WkbGeometryType -> Bool
$c/= :: WkbGeometryType -> WkbGeometryType -> Bool
== :: WkbGeometryType -> WkbGeometryType -> Bool
$c== :: WkbGeometryType -> WkbGeometryType -> Bool
Eq)
getWkbGeom :: Endian.EndianType -> BinaryGet.Get WkbGeometryType
getWkbGeom :: EndianType -> Get WkbGeometryType
getWkbGeom EndianType
endianType = do
Word32
fullGeometryType <- EndianType -> Get Word32
Endian.getFourBytes EndianType
endianType
let geomType :: Maybe GeometryType
geomType = Word32 -> Maybe GeometryType
intToGeometryType (Word32 -> Maybe GeometryType) -> Word32 -> Maybe GeometryType
forall a b. (a -> b) -> a -> b
$ Word32
fullGeometryType Word32 -> Word32 -> Word32
forall a. Integral a => a -> a -> a
`rem` Word32
1000
coordType :: Maybe CoordinateType
coordType = Word32 -> Maybe CoordinateType
intToCoordinateType (Word32 -> Maybe CoordinateType) -> Word32 -> Maybe CoordinateType
forall a b. (a -> b) -> a -> b
$ Word32
fullGeometryType Word32 -> Word32 -> Word32
forall a. Integral a => a -> a -> a
`div` Word32
1000
case (Maybe GeometryType
geomType, Maybe CoordinateType
coordType) of
(Just GeometryType
g, Just CoordinateType
c) -> WkbGeometryType -> Get WkbGeometryType
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WkbGeometryType -> Get WkbGeometryType)
-> WkbGeometryType -> Get WkbGeometryType
forall a b. (a -> b) -> a -> b
$ GeometryType -> CoordinateType -> WkbGeometryType
WkbGeom GeometryType
g CoordinateType
c
(Maybe GeometryType, Maybe CoordinateType)
_ ->
String -> Get WkbGeometryType
forall (m :: * -> *) a. MonadFail m => String -> m a
Monad.fail (String -> Get WkbGeometryType) -> String -> Get WkbGeometryType
forall a b. (a -> b) -> a -> b
$ String
"Invalid WkbGeometryType: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word32 -> String
forall a. Show a => a -> String
show Word32
fullGeometryType
type BuilderWkbGeometryType = Endian.EndianType -> WkbGeometryType -> ByteStringBuilder.Builder
builderWkbGeom :: Endian.EndianType -> WkbGeometryType -> ByteStringBuilder.Builder
builderWkbGeom :: EndianType -> WkbGeometryType -> Builder
builderWkbGeom EndianType
endianType (WkbGeom GeometryType
geometryType CoordinateType
coordinateType) = do
let int :: Word32
int = CoordinateType -> Word32
coordinateTypeToInt CoordinateType
coordinateType Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
* Word32
1000 Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ GeometryType -> Word32
geometryTypeToInt GeometryType
geometryType
EndianType -> Word32 -> Builder
Endian.builderFourBytes EndianType
endianType Word32
int
geoPositionWithoutCRSToCoordinateType :: Geospatial.GeoPositionWithoutCRS -> Maybe CoordinateType
geoPositionWithoutCRSToCoordinateType :: GeoPositionWithoutCRS -> Maybe CoordinateType
geoPositionWithoutCRSToCoordinateType GeoPositionWithoutCRS
geoPosition =
case GeoPositionWithoutCRS
geoPosition of
GeoPositionWithoutCRS
Geospatial.GeoEmpty -> Maybe CoordinateType
forall a. Maybe a
Nothing
Geospatial.GeoPointXY PointXY
_ -> CoordinateType -> Maybe CoordinateType
forall a. a -> Maybe a
Just CoordinateType
TwoD
Geospatial.GeoPointXYZ PointXYZ
_ -> CoordinateType -> Maybe CoordinateType
forall a. a -> Maybe a
Just CoordinateType
Z
Geospatial.GeoPointXYZM PointXYZM
_ -> CoordinateType -> Maybe CoordinateType
forall a. a -> Maybe a
Just CoordinateType
ZM
coordTypeOfSequence :: Sequence.Seq Geospatial.GeoPositionWithoutCRS -> CoordinateType
coordTypeOfSequence :: Seq GeoPositionWithoutCRS -> CoordinateType
coordTypeOfSequence (GeoPositionWithoutCRS
first Sequence.:<| Seq GeoPositionWithoutCRS
_) =
CoordinateType -> Maybe CoordinateType -> CoordinateType
forall a. a -> Maybe a -> a
Maybe.fromMaybe CoordinateType
TwoD (GeoPositionWithoutCRS -> Maybe CoordinateType
geoPositionWithoutCRSToCoordinateType GeoPositionWithoutCRS
first)
coordTypeOfSequence Seq GeoPositionWithoutCRS
_ = CoordinateType
TwoD
coordTypeOfLinearRings :: Sequence.Seq (LinearRing.LinearRing Geospatial.GeoPositionWithoutCRS) -> CoordinateType
coordTypeOfLinearRings :: Seq (LinearRing GeoPositionWithoutCRS) -> CoordinateType
coordTypeOfLinearRings (LinearRing GeoPositionWithoutCRS
first Sequence.:<| Seq (LinearRing GeoPositionWithoutCRS)
_) = Seq GeoPositionWithoutCRS -> CoordinateType
coordTypeOfSequence (Seq GeoPositionWithoutCRS -> CoordinateType)
-> Seq GeoPositionWithoutCRS -> CoordinateType
forall a b. (a -> b) -> a -> b
$ LinearRing GeoPositionWithoutCRS -> Seq GeoPositionWithoutCRS
forall a. LinearRing a -> Seq a
LinearRing.toSeq LinearRing GeoPositionWithoutCRS
first
coordTypeOfLinearRings Seq (LinearRing GeoPositionWithoutCRS)
_ = CoordinateType
TwoD
intToGeometryType :: Word.Word32 -> Maybe GeometryType
intToGeometryType :: Word32 -> Maybe GeometryType
intToGeometryType Word32
int =
case Word32
int of
Word32
0 -> GeometryType -> Maybe GeometryType
forall a. a -> Maybe a
Just GeometryType
Geometry
Word32
1 -> GeometryType -> Maybe GeometryType
forall a. a -> Maybe a
Just GeometryType
Point
Word32
2 -> GeometryType -> Maybe GeometryType
forall a. a -> Maybe a
Just GeometryType
LineString
Word32
3 -> GeometryType -> Maybe GeometryType
forall a. a -> Maybe a
Just GeometryType
Polygon
Word32
4 -> GeometryType -> Maybe GeometryType
forall a. a -> Maybe a
Just GeometryType
MultiPoint
Word32
5 -> GeometryType -> Maybe GeometryType
forall a. a -> Maybe a
Just GeometryType
MultiLineString
Word32
6 -> GeometryType -> Maybe GeometryType
forall a. a -> Maybe a
Just GeometryType
MultiPolygon
Word32
7 -> GeometryType -> Maybe GeometryType
forall a. a -> Maybe a
Just GeometryType
GeometryCollection
Word32
_ -> Maybe GeometryType
forall a. Maybe a
Nothing
geometryTypeToInt :: GeometryType -> Word.Word32
geometryTypeToInt :: GeometryType -> Word32
geometryTypeToInt GeometryType
geometryType =
case GeometryType
geometryType of
GeometryType
Geometry -> Word32
0
GeometryType
Point -> Word32
1
GeometryType
LineString -> Word32
2
GeometryType
Polygon -> Word32
3
GeometryType
MultiPoint -> Word32
4
GeometryType
MultiLineString -> Word32
5
GeometryType
MultiPolygon -> Word32
6
GeometryType
GeometryCollection -> Word32
7
intToCoordinateType :: Word.Word32 -> Maybe CoordinateType
intToCoordinateType :: Word32 -> Maybe CoordinateType
intToCoordinateType Word32
int =
case Word32
int of
Word32
0 -> CoordinateType -> Maybe CoordinateType
forall a. a -> Maybe a
Just CoordinateType
TwoD
Word32
1 -> CoordinateType -> Maybe CoordinateType
forall a. a -> Maybe a
Just CoordinateType
Z
Word32
2 -> CoordinateType -> Maybe CoordinateType
forall a. a -> Maybe a
Just CoordinateType
M
Word32
3 -> CoordinateType -> Maybe CoordinateType
forall a. a -> Maybe a
Just CoordinateType
ZM
Word32
_ -> Maybe CoordinateType
forall a. Maybe a
Nothing
coordinateTypeToInt :: CoordinateType -> Word.Word32
coordinateTypeToInt :: CoordinateType -> Word32
coordinateTypeToInt CoordinateType
coordinateType =
case CoordinateType
coordinateType of
CoordinateType
TwoD -> Word32
0
CoordinateType
Z -> Word32
1
CoordinateType
M -> Word32
2
CoordinateType
ZM -> Word32
3