Copyright | (C) 2014-2018 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
- type GeoPositionWithoutCRS = [Double]
- data GeoPosition
- newtype GeoPoint = GeoPoint {}
- newtype GeoMultiPoint = GeoMultiPoint {}
- splitGeoMultiPoint :: GeoMultiPoint -> [GeoPoint]
- mergeGeoPoints :: [GeoPoint] -> GeoMultiPoint
- newtype GeoPolygon = GeoPolygon {}
- newtype GeoMultiPolygon = GeoMultiPolygon {}
- splitGeoMultiPolygon :: GeoMultiPolygon -> [GeoPolygon]
- mergeGeoPolygons :: [GeoPolygon] -> GeoMultiPolygon
- newtype GeoLine = GeoLine {}
- newtype GeoMultiLine = GeoMultiLine {}
- splitGeoMultiLine :: GeoMultiLine -> [GeoLine]
- mergeGeoLines :: [GeoLine] -> GeoMultiLine
- data GeospatialGeometry
- type Name = Text
- type Code = Int
- type Href = Text
- type FormatString = Text
- type ProjectionType = Text
- data CRSObject
- type BoundingBoxWithoutCRS = [Double]
- data GeoFeature a = GeoFeature {}
- data GeoFeatureCollection a = GeoFeatureCollection {}
- stripCRSFromPosition :: GeoPosition -> GeoPositionWithoutCRS
- defaultCRS :: CRSObject
- unGeoPoint :: Iso' GeoPoint GeoPositionWithoutCRS
- unGeoMultiPoint :: Iso' GeoMultiPoint [GeoPositionWithoutCRS]
- unGeoPolygon :: Iso' GeoPolygon [LinearRing GeoPositionWithoutCRS]
- unGeoLine :: Iso' GeoLine (LineString GeoPositionWithoutCRS)
- unGeoMultiLine :: Iso' GeoMultiLine [LineString GeoPositionWithoutCRS]
- unGeoMultiPolygon :: Iso' GeoMultiPolygon [[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) [GeoFeature a] [GeoFeature a]
- _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 [GeospatialGeometry]
- _NoCRS :: Prism' CRSObject ()
- _NamedCRS :: Prism' CRSObject Name
- _EPSG :: Prism' CRSObject Code
- _LinkedCRS :: Prism' CRSObject (Href, FormatString)
Types
type GeoPositionWithoutCRS = [Double] Source #
(GeoPositionWithoutCRS
is a catch all for indeterminate CRSs and for expression of positions
before a CRS has been determined
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)
newtype GeoMultiPoint Source #
Instances
Eq GeoMultiPoint Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint (==) :: GeoMultiPoint -> GeoMultiPoint -> Bool # (/=) :: GeoMultiPoint -> GeoMultiPoint -> Bool # | |
Show GeoMultiPoint Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint showsPrec :: Int -> GeoMultiPoint -> ShowS # show :: GeoMultiPoint -> String # showList :: [GeoMultiPoint] -> ShowS # | |
ToJSON GeoMultiPoint Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint toJSON :: GeoMultiPoint -> Value # toEncoding :: GeoMultiPoint -> Encoding # toJSONList :: [GeoMultiPoint] -> Value # toEncodingList :: [GeoMultiPoint] -> Encoding # | |
FromJSON GeoMultiPoint Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint parseJSON :: Value -> Parser GeoMultiPoint # parseJSONList :: Value -> Parser [GeoMultiPoint] # |
splitGeoMultiPoint :: GeoMultiPoint -> [GeoPoint] Source #
Split GeoMultiPoint coordinates into multiple GeoPoints
mergeGeoPoints :: [GeoPoint] -> GeoMultiPoint Source #
Merge multiple GeoPoints into one GeoMultiPoint
newtype GeoPolygon Source #
Instances
Eq GeoPolygon Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoPolygon (==) :: GeoPolygon -> GeoPolygon -> Bool # (/=) :: GeoPolygon -> GeoPolygon -> Bool # | |
Show GeoPolygon Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoPolygon showsPrec :: Int -> GeoPolygon -> ShowS # show :: GeoPolygon -> String # showList :: [GeoPolygon] -> ShowS # | |
ToJSON GeoPolygon Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoPolygon toJSON :: GeoPolygon -> Value # toEncoding :: GeoPolygon -> Encoding # toJSONList :: [GeoPolygon] -> Value # toEncodingList :: [GeoPolygon] -> Encoding # | |
FromJSON GeoPolygon Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoPolygon parseJSON :: Value -> Parser GeoPolygon # parseJSONList :: Value -> Parser [GeoPolygon] # |
newtype GeoMultiPolygon Source #
Instances
Eq GeoMultiPolygon Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon (==) :: GeoMultiPolygon -> GeoMultiPolygon -> Bool # (/=) :: GeoMultiPolygon -> GeoMultiPolygon -> Bool # | |
Show GeoMultiPolygon Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon showsPrec :: Int -> GeoMultiPolygon -> ShowS # show :: GeoMultiPolygon -> String # showList :: [GeoMultiPolygon] -> ShowS # | |
ToJSON GeoMultiPolygon Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon toJSON :: GeoMultiPolygon -> Value # toEncoding :: GeoMultiPolygon -> Encoding # toJSONList :: [GeoMultiPolygon] -> Value # toEncodingList :: [GeoMultiPolygon] -> Encoding # | |
FromJSON GeoMultiPolygon Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon parseJSON :: Value -> Parser GeoMultiPolygon # parseJSONList :: Value -> Parser [GeoMultiPolygon] # |
splitGeoMultiPolygon :: GeoMultiPolygon -> [GeoPolygon] Source #
Split GeoMultiPolygon coordinates into multiple GeoPolygons
mergeGeoPolygons :: [GeoPolygon] -> GeoMultiPolygon Source #
Merge multiple GeoPolygons into one GeoMultiPolygon
newtype GeoMultiLine Source #
Instances
Eq GeoMultiLine Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine (==) :: GeoMultiLine -> GeoMultiLine -> Bool # (/=) :: GeoMultiLine -> GeoMultiLine -> Bool # | |
Show GeoMultiLine Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine showsPrec :: Int -> GeoMultiLine -> ShowS # show :: GeoMultiLine -> String # showList :: [GeoMultiLine] -> ShowS # | |
ToJSON GeoMultiLine Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine toJSON :: GeoMultiLine -> Value # toEncoding :: GeoMultiLine -> Encoding # toJSONList :: [GeoMultiLine] -> Value # toEncodingList :: [GeoMultiLine] -> Encoding # | |
FromJSON GeoMultiLine Source # | |
Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine parseJSON :: Value -> Parser GeoMultiLine # parseJSONList :: Value -> Parser [GeoMultiLine] # |
splitGeoMultiLine :: GeoMultiLine -> [GeoLine] Source #
Split GeoMultiLine coordinates into multiple GeoLines
mergeGeoLines :: [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 [GeospatialGeometry] |
Instances
Eq GeospatialGeometry Source # | |
Defined in Data.Geospatial.Internal.Geometry (==) :: GeospatialGeometry -> GeospatialGeometry -> Bool # (/=) :: GeospatialGeometry -> GeospatialGeometry -> Bool # | |
Show GeospatialGeometry Source # | |
Defined in Data.Geospatial.Internal.Geometry showsPrec :: Int -> GeospatialGeometry -> ShowS # show :: GeospatialGeometry -> String # showList :: [GeospatialGeometry] -> ShowS # | |
ToJSON GeospatialGeometry Source # | encodes Geometry Objects to GeoJSON |
Defined in Data.Geospatial.Internal.Geometry toJSON :: GeospatialGeometry -> Value # toEncoding :: GeospatialGeometry -> Encoding # toJSONList :: [GeospatialGeometry] -> Value # toEncodingList :: [GeospatialGeometry] -> Encoding # | |
FromJSON GeospatialGeometry Source # | decodes Geometry Objects from GeoJSON Aeson doesnt decode "null" into |
Defined in Data.Geospatial.Internal.Geometry parseJSON :: Value -> Parser GeospatialGeometry # parseJSONList :: Value -> Parser [GeospatialGeometry] # |
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
type BoundingBoxWithoutCRS = [Double] 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.
data GeoFeature a Source #
See Section 2.2 Feature Objects of the GeoJSON spec. Parameterised on the property type
Instances
Eq a => Eq (GeoFeature a) Source # | |
Defined in Data.Geospatial.Internal.GeoFeature (==) :: GeoFeature a -> GeoFeature a -> Bool # (/=) :: GeoFeature a -> GeoFeature a -> Bool # | |
Show a => Show (GeoFeature a) Source # | |
Defined in Data.Geospatial.Internal.GeoFeature showsPrec :: Int -> GeoFeature a -> ShowS # show :: GeoFeature a -> String # showList :: [GeoFeature a] -> ShowS # | |
ToJSON a => ToJSON (GeoFeature a) Source # | Encodes Feature objects to GeoJSON |
Defined in Data.Geospatial.Internal.GeoFeature toJSON :: GeoFeature a -> Value # toEncoding :: GeoFeature a -> Encoding # toJSONList :: [GeoFeature a] -> Value # toEncodingList :: [GeoFeature a] -> Encoding # | |
FromJSON a => FromJSON (GeoFeature a) Source # | Decodes Feature objects from GeoJSON |
Defined in Data.Geospatial.Internal.GeoFeature parseJSON :: Value -> Parser (GeoFeature a) # parseJSONList :: Value -> Parser [GeoFeature a] # |
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) [GeoFeature a] [GeoFeature a] Source #
Prisms
Geometry
CRS
_LinkedCRS :: Prism' CRSObject (Href, FormatString) Source #