Copyright | (C) 2014-2019 HS-GeoJSON Project |
---|---|
License | BSD-style (see the file LICENSE.md) |
Maintainer | Andrew Newman |
Safe Haskell | None |
Language | Haskell2010 |
Refer to the GeoJSON Spec http://www.geojson.org/geojson-spec.html
Synopsis
- type Latitude = Double
- type Longitude = Double
- type Easting = Double
- type Northing = Double
- type Altitude = Double
- data FeatureID
- data GeoPositionWithoutCRS
- data GeoPosition
- newtype GeoPoint = GeoPoint {}
- retrieveXY :: GeoPositionWithoutCRS -> PointXY
- data PointXY = PointXY {}
- data PointXYZ = PointXYZ {}
- data PointXYZM = PointXYZM {}
- newtype GeoMultiPoint = GeoMultiPoint {}
- splitGeoMultiPoint :: GeoMultiPoint -> Seq GeoPoint
- mergeGeoPoints :: Seq GeoPoint -> GeoMultiPoint
- newtype GeoPolygon = GeoPolygon {}
- newtype GeoMultiPolygon = GeoMultiPolygon {}
- splitGeoMultiPolygon :: GeoMultiPolygon -> Seq GeoPolygon
- mergeGeoPolygons :: Seq GeoPolygon -> GeoMultiPolygon
- newtype GeoLine = GeoLine {}
- newtype GeoMultiLine = GeoMultiLine {}
- splitGeoMultiLine :: GeoMultiLine -> Seq GeoLine
- mergeGeoLines :: Seq GeoLine -> GeoMultiLine
- data GeospatialGeometry
- type Name = Text
- type Code = Int
- type Href = Text
- type FormatString = Text
- type ProjectionType = Text
- data CRSObject
- data BoundingBoxWithoutCRS
- data GeoFeature a = GeoFeature {}
- reWrapGeometry :: GeoFeature a -> GeospatialGeometry -> GeoFeature a
- data GeoFeatureCollection a = GeoFeatureCollection {}
- stripCRSFromPosition :: GeoPosition -> GeoPositionWithoutCRS
- defaultCRS :: CRSObject
- unGeoPoint :: Iso' GeoPoint GeoPositionWithoutCRS
- unGeoMultiPoint :: Iso' GeoMultiPoint (Seq GeoPositionWithoutCRS)
- unGeoPolygon :: Iso' GeoPolygon (Seq (LinearRing GeoPositionWithoutCRS))
- unGeoLine :: Iso' GeoLine (LineString GeoPositionWithoutCRS)
- unGeoMultiLine :: Iso' GeoMultiLine (Seq (LineString GeoPositionWithoutCRS))
- unGeoMultiPolygon :: Iso' GeoMultiPolygon (Seq (Seq (LinearRing GeoPositionWithoutCRS)))
- bbox :: forall a. Lens' (GeoFeature a) (Maybe BoundingBoxWithoutCRS)
- geometry :: forall a. Lens' (GeoFeature a) GeospatialGeometry
- properties :: forall a a. Lens (GeoFeature a) (GeoFeature a) a a
- featureId :: forall a. Lens' (GeoFeature a) (Maybe FeatureID)
- boundingbox :: forall a. Lens' (GeoFeatureCollection a) (Maybe BoundingBoxWithoutCRS)
- geofeatures :: forall a a. Lens (GeoFeatureCollection a) (GeoFeatureCollection a) (Seq (GeoFeature a)) (Seq (GeoFeature a))
- class HasGeoPositionWithoutCRS c where
- _NoGeometry :: Prism' GeospatialGeometry ()
- _Point :: Prism' GeospatialGeometry GeoPoint
- _MultiPoint :: Prism' GeospatialGeometry GeoMultiPoint
- _Polygon :: Prism' GeospatialGeometry GeoPolygon
- _MultiPolygon :: Prism' GeospatialGeometry GeoMultiPolygon
- _Line :: Prism' GeospatialGeometry GeoLine
- _MultiLine :: Prism' GeospatialGeometry GeoMultiLine
- _Collection :: Prism' GeospatialGeometry (Seq GeospatialGeometry)
- _NoCRS :: Prism' CRSObject ()
- _NamedCRS :: Prism' CRSObject Name
- _EPSG :: Prism' CRSObject Code
- _LinkedCRS :: Prism' CRSObject (Href, FormatString)
Types
Instances
Eq FeatureID Source # | |
Show FeatureID Source # | |
Generic FeatureID Source # | |
ToJSON FeatureID Source # | |
Defined in Data.Geospatial.Internal.BasicTypes | |
FromJSON FeatureID Source # | |
NFData FeatureID Source # | |
Defined in Data.Geospatial.Internal.BasicTypes | |
type Rep FeatureID Source # | |
Defined in Data.Geospatial.Internal.BasicTypes type Rep FeatureID = D1 (MetaData "FeatureID" "Data.Geospatial.Internal.BasicTypes" "geojson-4.0.2-EXHv8i4JQwXM7d3a9DXxR" False) (C1 (MetaCons "FeatureIDText" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "FeatureIDNumber" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) |
data GeoPositionWithoutCRS Source #
Instances
data GeoPosition Source #
see Section 2.1.1 Position in the GeoJSON Spec, I make the assumption here that the only position types we will use will involve easting or northing (+ve or -ve Altitude) or lon or lat (+ve or -ve Altitude)
Instances
Eq GeoPoint Source # | |
Show GeoPoint Source # | |
Generic GeoPoint Source # | |
ToJSON GeoPoint Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoPoint | |
FromJSON GeoPoint Source # | |
NFData GeoPoint Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoPoint | |
type Rep GeoPoint Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoPoint type Rep GeoPoint = D1 (MetaData "GeoPoint" "Data.Geospatial.Internal.Geometry.GeoPoint" "geojson-4.0.2-EXHv8i4JQwXM7d3a9DXxR" True) (C1 (MetaCons "GeoPoint" PrefixI True) (S1 (MetaSel (Just "_unGeoPoint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GeoPositionWithoutCRS))) |
(GeoPositionWithoutCRS
is a catch all for indeterminate CRSs and for expression of positions
before a CRS has been determined
Instances
Eq PointXY Source # | |
Show PointXY Source # | |
Generic PointXY Source # | |
NFData PointXY Source # | |
Defined in Data.Geospatial.Internal.BasicTypes | |
type Rep PointXY Source # | |
Defined in Data.Geospatial.Internal.BasicTypes type Rep PointXY = D1 (MetaData "PointXY" "Data.Geospatial.Internal.BasicTypes" "geojson-4.0.2-EXHv8i4JQwXM7d3a9DXxR" False) (C1 (MetaCons "PointXY" PrefixI True) (S1 (MetaSel (Just "_xyX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "_xyY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) |
Instances
Eq PointXYZ Source # | |
Show PointXYZ Source # | |
Generic PointXYZ Source # | |
NFData PointXYZ Source # | |
Defined in Data.Geospatial.Internal.BasicTypes | |
type Rep PointXYZ Source # | |
Defined in Data.Geospatial.Internal.BasicTypes type Rep PointXYZ = D1 (MetaData "PointXYZ" "Data.Geospatial.Internal.BasicTypes" "geojson-4.0.2-EXHv8i4JQwXM7d3a9DXxR" False) (C1 (MetaCons "PointXYZ" PrefixI True) (S1 (MetaSel (Just "_xyzX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: (S1 (MetaSel (Just "_xyzY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "_xyzZ") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))) |
Instances
Eq PointXYZM Source # | |
Show PointXYZM Source # | |
Generic PointXYZM Source # | |
NFData PointXYZM Source # | |
Defined in Data.Geospatial.Internal.BasicTypes | |
type Rep PointXYZM Source # | |
Defined in Data.Geospatial.Internal.BasicTypes type Rep PointXYZM = D1 (MetaData "PointXYZM" "Data.Geospatial.Internal.BasicTypes" "geojson-4.0.2-EXHv8i4JQwXM7d3a9DXxR" False) (C1 (MetaCons "PointXYZM" PrefixI True) ((S1 (MetaSel (Just "_xyzmX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "_xyzmY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Just "_xyzmZ") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "_xyzmM") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))) |
newtype GeoMultiPoint Source #
Instances
splitGeoMultiPoint :: GeoMultiPoint -> Seq GeoPoint Source #
Split GeoMultiPoint coordinates into multiple GeoPoints
mergeGeoPoints :: Seq GeoPoint -> GeoMultiPoint Source #
Merge multiple GeoPoints into one GeoMultiPoint
newtype GeoPolygon Source #
Instances
newtype GeoMultiPolygon Source #
Instances
splitGeoMultiPolygon :: GeoMultiPolygon -> Seq GeoPolygon Source #
Split GeoMultiPolygon coordinates into multiple GeoPolygons
mergeGeoPolygons :: Seq GeoPolygon -> GeoMultiPolygon Source #
Merge multiple GeoPolygons into one GeoMultiPolygon
Instances
Eq GeoLine Source # | |
Show GeoLine Source # | |
Generic GeoLine Source # | |
ToJSON GeoLine Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoLine | |
FromJSON GeoLine Source # | |
NFData GeoLine Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoLine | |
type Rep GeoLine Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoLine type Rep GeoLine = D1 (MetaData "GeoLine" "Data.Geospatial.Internal.Geometry.GeoLine" "geojson-4.0.2-EXHv8i4JQwXM7d3a9DXxR" True) (C1 (MetaCons "GeoLine" PrefixI True) (S1 (MetaSel (Just "_unGeoLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (LineString GeoPositionWithoutCRS)))) |
newtype GeoMultiLine Source #
Instances
splitGeoMultiLine :: GeoMultiLine -> Seq GeoLine Source #
Split GeoMultiLine coordinates into multiple GeoLines
mergeGeoLines :: Seq GeoLine -> GeoMultiLine Source #
Merge multiple GeoLines into one GeoMultiLine
data GeospatialGeometry Source #
See section 2.1 Geometry Objects in the GeoJSON Spec.
NoGeometry | |
Point GeoPoint | |
MultiPoint GeoMultiPoint | |
Polygon GeoPolygon | |
MultiPolygon GeoMultiPolygon | |
Line GeoLine | |
MultiLine GeoMultiLine | |
Collection (Seq GeospatialGeometry) |
Instances
type FormatString = Text Source #
type ProjectionType = Text Source #
See Section 3 Coordinate Reference System Objects in the GeoJSON Spec
NoCRS
is required because no crs
attribute in a GeoJSON feature is NOT the same thing as
a null crs
attribute. no crs
value implies the default CRS, while a null CRS means
you cannot assume a CRS, null will mapped to NoCRS
while a non-existent attribute will
be mapped to a Nothing
Maybe
value
data BoundingBoxWithoutCRS Source #
See Section 4 Bounding Boxes of the GeoJSON spec, The length of the list/array must be 2*n where n is the dimensionality of the position type for the CRS with min values first followed by the max values, wich both the min/max sets following the same axis order as the CRS, e.g for WGS84: minLongitude, minLatitude, maxLongitude, maxLatitude The spec mentions that it can be part of a geometry object too but doesnt give an example, This implementation will ignore bboxes on Geometry objects, they can be added if required.
BoundingBoxWithoutCRSXY PointXY PointXY | |
BoundingBoxWithoutCRSXYZ PointXYZ PointXYZ | |
BoundingBoxWithoutCRSXYZM PointXYZM PointXYZM |
Instances
data GeoFeature a Source #
See Section 2.2 Feature Objects of the GeoJSON spec. Parameterised on the property type
Instances
reWrapGeometry :: GeoFeature a -> GeospatialGeometry -> GeoFeature a Source #
data GeoFeatureCollection a Source #
See Section 2.3 Feature Collection Objects of the GeoJSON spec
Instances
Functions
stripCRSFromPosition :: GeoPosition -> GeoPositionWithoutCRS Source #
the GeoPosition
is a bit special in that when you convert it to GeoJSON,
it will lose the CRS info attached to it and cannot be read back in
from the GeoJSON. Hence it is ineligible for the FromJSON
type class,
so this function will strip it down to a GeoPositionWithoutCRS
, which is eligible
defaultCRS :: CRSObject Source #
The default CRS according to Section 3 Coordinate Reference System Objects is WGS84 which I believe, from http://spatialreference.org/ref/epsg/4326/ which translates to this in JSON: http://spatialreference.org/ref/epsg/4326/json/) is represented thus:
Lenses
Geometry Lenses
Feature Lenses
bbox :: forall a. Lens' (GeoFeature a) (Maybe BoundingBoxWithoutCRS) Source #
geometry :: forall a. Lens' (GeoFeature a) GeospatialGeometry Source #
properties :: forall a a. Lens (GeoFeature a) (GeoFeature a) a a Source #
boundingbox :: forall a. Lens' (GeoFeatureCollection a) (Maybe BoundingBoxWithoutCRS) Source #
geofeatures :: forall a a. Lens (GeoFeatureCollection a) (GeoFeatureCollection a) (Seq (GeoFeature a)) (Seq (GeoFeature a)) Source #
Prisms
BasicTypes
class HasGeoPositionWithoutCRS c where Source #
Geometry
CRS
_LinkedCRS :: Prism' CRSObject (Href, FormatString) Source #