geojson-4.0.0: A thin GeoJSON Layer above the aeson library

Copyright(C) 2014-2018 HS-GeoJSON Project
LicenseBSD-style (see the file LICENSE.md)
MaintainerAndrew Newman
Safe HaskellNone
LanguageHaskell2010

Data.Geospatial

Contents

Description

Synopsis

Types

data FeatureID Source #

Instances
Eq FeatureID Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Show FeatureID Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Generic FeatureID Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Associated Types

type Rep FeatureID :: * -> * #

ToJSON FeatureID Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

FromJSON FeatureID Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

NFData FeatureID Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Methods

rnf :: FeatureID -> () #

type Rep FeatureID Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

type Rep FeatureID = D1 (MetaData "FeatureID" "Data.Geospatial.Internal.BasicTypes" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" 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
Eq GeoPositionWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Show GeoPositionWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Generic GeoPositionWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Associated Types

type Rep GeoPositionWithoutCRS :: * -> * #

ToJSON GeoPositionWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

FromJSON GeoPositionWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

NFData GeoPositionWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Methods

rnf :: GeoPositionWithoutCRS -> () #

HasGeoPositionWithoutCRS GeoPositionWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

type Rep GeoPositionWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

type Rep GeoPositionWithoutCRS = D1 (MetaData "GeoPositionWithoutCRS" "Data.Geospatial.Internal.BasicTypes" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" False) ((C1 (MetaCons "GeoEmpty" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "GeoPointXY" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PointXY))) :+: (C1 (MetaCons "GeoPointXYZ" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PointXYZ)) :+: C1 (MetaCons "GeoPointXYZM" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PointXYZM))))

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 GeoPoint Source #

Instances
Eq GeoPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPoint

Show GeoPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPoint

Generic GeoPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPoint

Associated Types

type Rep GeoPoint :: * -> * #

Methods

from :: GeoPoint -> Rep GeoPoint x #

to :: Rep GeoPoint x -> GeoPoint #

ToJSON GeoPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPoint

FromJSON GeoPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPoint

NFData GeoPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPoint

Methods

rnf :: GeoPoint -> () #

type Rep GeoPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPoint

type Rep GeoPoint = D1 (MetaData "GeoPoint" "Data.Geospatial.Internal.Geometry.GeoPoint" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" True) (C1 (MetaCons "GeoPoint" PrefixI True) (S1 (MetaSel (Just "_unGeoPoint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GeoPositionWithoutCRS)))

data PointXY Source #

(GeoPositionWithoutCRS is a catch all for indeterminate CRSs and for expression of positions before a CRS has been determined

Constructors

PointXY 

Fields

Instances
Eq PointXY Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Methods

(==) :: PointXY -> PointXY -> Bool #

(/=) :: PointXY -> PointXY -> Bool #

Show PointXY Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Generic PointXY Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Associated Types

type Rep PointXY :: * -> * #

Methods

from :: PointXY -> Rep PointXY x #

to :: Rep PointXY x -> PointXY #

NFData PointXY Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Methods

rnf :: PointXY -> () #

type Rep PointXY Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

type Rep PointXY = D1 (MetaData "PointXY" "Data.Geospatial.Internal.BasicTypes" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" False) (C1 (MetaCons "PointXY" PrefixI True) (S1 (MetaSel (Just "_xyX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "_xyY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)))

data PointXYZ Source #

Constructors

PointXYZ 

Fields

Instances
Eq PointXYZ Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Show PointXYZ Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Generic PointXYZ Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Associated Types

type Rep PointXYZ :: * -> * #

Methods

from :: PointXYZ -> Rep PointXYZ x #

to :: Rep PointXYZ x -> PointXYZ #

NFData PointXYZ Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Methods

rnf :: PointXYZ -> () #

type Rep PointXYZ Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

type Rep PointXYZ = D1 (MetaData "PointXYZ" "Data.Geospatial.Internal.BasicTypes" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" 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))))

data PointXYZM Source #

Constructors

PointXYZM 

Fields

Instances
Eq PointXYZM Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Show PointXYZM Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Generic PointXYZM Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Associated Types

type Rep PointXYZM :: * -> * #

NFData PointXYZM Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Methods

rnf :: PointXYZM -> () #

type Rep PointXYZM Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

type Rep PointXYZM = D1 (MetaData "PointXYZM" "Data.Geospatial.Internal.BasicTypes" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" 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
Eq GeoMultiPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint

Show GeoMultiPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint

Generic GeoMultiPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint

Associated Types

type Rep GeoMultiPoint :: * -> * #

ToJSON GeoMultiPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint

FromJSON GeoMultiPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint

NFData GeoMultiPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint

Methods

rnf :: GeoMultiPoint -> () #

type Rep GeoMultiPoint Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPoint

type Rep GeoMultiPoint = D1 (MetaData "GeoMultiPoint" "Data.Geospatial.Internal.Geometry.GeoMultiPoint" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" True) (C1 (MetaCons "GeoMultiPoint" PrefixI True) (S1 (MetaSel (Just "_unGeoMultiPoint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Seq GeoPositionWithoutCRS))))

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
Eq GeoPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPolygon

Show GeoPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPolygon

Generic GeoPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPolygon

Associated Types

type Rep GeoPolygon :: * -> * #

ToJSON GeoPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPolygon

FromJSON GeoPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPolygon

NFData GeoPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPolygon

Methods

rnf :: GeoPolygon -> () #

type Rep GeoPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoPolygon

type Rep GeoPolygon = D1 (MetaData "GeoPolygon" "Data.Geospatial.Internal.Geometry.GeoPolygon" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" True) (C1 (MetaCons "GeoPolygon" PrefixI True) (S1 (MetaSel (Just "_unGeoPolygon") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Seq (LinearRing GeoPositionWithoutCRS)))))

newtype GeoMultiPolygon Source #

Instances
Eq GeoMultiPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon

Show GeoMultiPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon

Generic GeoMultiPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon

Associated Types

type Rep GeoMultiPolygon :: * -> * #

ToJSON GeoMultiPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon

FromJSON GeoMultiPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon

NFData GeoMultiPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon

Methods

rnf :: GeoMultiPolygon -> () #

type Rep GeoMultiPolygon Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiPolygon

type Rep GeoMultiPolygon = D1 (MetaData "GeoMultiPolygon" "Data.Geospatial.Internal.Geometry.GeoMultiPolygon" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" True) (C1 (MetaCons "GeoMultiPolygon" PrefixI True) (S1 (MetaSel (Just "_unGeoMultiPolygon") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Seq (Seq (LinearRing GeoPositionWithoutCRS))))))

splitGeoMultiPolygon :: GeoMultiPolygon -> Seq GeoPolygon Source #

Split GeoMultiPolygon coordinates into multiple GeoPolygons

mergeGeoPolygons :: Seq GeoPolygon -> GeoMultiPolygon Source #

Merge multiple GeoPolygons into one GeoMultiPolygon

newtype GeoLine Source #

Instances
Eq GeoLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoLine

Methods

(==) :: GeoLine -> GeoLine -> Bool #

(/=) :: GeoLine -> GeoLine -> Bool #

Show GeoLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoLine

Generic GeoLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoLine

Associated Types

type Rep GeoLine :: * -> * #

Methods

from :: GeoLine -> Rep GeoLine x #

to :: Rep GeoLine x -> GeoLine #

ToJSON GeoLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoLine

FromJSON GeoLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoLine

NFData GeoLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoLine

Methods

rnf :: GeoLine -> () #

type Rep GeoLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoLine

type Rep GeoLine = D1 (MetaData "GeoLine" "Data.Geospatial.Internal.Geometry.GeoLine" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" True) (C1 (MetaCons "GeoLine" PrefixI True) (S1 (MetaSel (Just "_unGeoLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (LineString GeoPositionWithoutCRS))))

newtype GeoMultiLine Source #

Instances
Eq GeoMultiLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine

Show GeoMultiLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine

Generic GeoMultiLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine

Associated Types

type Rep GeoMultiLine :: * -> * #

ToJSON GeoMultiLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine

FromJSON GeoMultiLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine

NFData GeoMultiLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine

Methods

rnf :: GeoMultiLine -> () #

type Rep GeoMultiLine Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry.GeoMultiLine

type Rep GeoMultiLine = D1 (MetaData "GeoMultiLine" "Data.Geospatial.Internal.Geometry.GeoMultiLine" "geojson-4.0.0-LfimOKHC7xkHG9PwcAUyY5" True) (C1 (MetaCons "GeoMultiLine" PrefixI True) (S1 (MetaSel (Just "_unGeoMultiLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Seq (LineString GeoPositionWithoutCRS)))))

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.

Instances
Eq GeospatialGeometry Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry

Show GeospatialGeometry Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry

Generic GeospatialGeometry Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry

Associated Types

type Rep GeospatialGeometry :: * -> * #

ToJSON GeospatialGeometry Source #

encodes Geometry Objects to GeoJSON

Instance details

Defined in Data.Geospatial.Internal.Geometry

FromJSON GeospatialGeometry Source #

decodes Geometry Objects from GeoJSON

Aeson doesnt decode "null" into Null unfortunately

Instance details

Defined in Data.Geospatial.Internal.Geometry

NFData GeospatialGeometry Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry

Methods

rnf :: GeospatialGeometry -> () #

type Rep GeospatialGeometry Source # 
Instance details

Defined in Data.Geospatial.Internal.Geometry

type Name = Text Source #

type Code = Int Source #

type Href = Text Source #

data CRSObject 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

Instances
Eq CRSObject Source # 
Instance details

Defined in Data.Geospatial.Internal.CRS

Show CRSObject Source # 
Instance details

Defined in Data.Geospatial.Internal.CRS

ToJSON CRSObject Source #

encode CRS Objects to GeoJSON

Instance details

Defined in Data.Geospatial.Internal.CRS

FromJSON CRSObject Source #

decode CRS Objects from GeoJSON

Aeson doesnt decode "null" to Null unfortunately

Instance details

Defined in Data.Geospatial.Internal.CRS

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.

Instances
Eq BoundingBoxWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Show BoundingBoxWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Generic BoundingBoxWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Associated Types

type Rep BoundingBoxWithoutCRS :: * -> * #

ToJSON BoundingBoxWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

FromJSON BoundingBoxWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

NFData BoundingBoxWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Methods

rnf :: BoundingBoxWithoutCRS -> () #

type Rep BoundingBoxWithoutCRS Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

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 # 
Instance details

Defined in Data.Geospatial.Internal.GeoFeature

Methods

(==) :: GeoFeature a -> GeoFeature a -> Bool #

(/=) :: GeoFeature a -> GeoFeature a -> Bool #

Show a => Show (GeoFeature a) Source # 
Instance details

Defined in Data.Geospatial.Internal.GeoFeature

Generic (GeoFeature a) Source # 
Instance details

Defined in Data.Geospatial.Internal.GeoFeature

Associated Types

type Rep (GeoFeature a) :: * -> * #

Methods

from :: GeoFeature a -> Rep (GeoFeature a) x #

to :: Rep (GeoFeature a) x -> GeoFeature a #

ToJSON a => ToJSON (GeoFeature a) Source #

Encodes Feature objects to GeoJSON

Instance details

Defined in Data.Geospatial.Internal.GeoFeature

FromJSON a => FromJSON (GeoFeature a) Source #

Decodes Feature objects from GeoJSON

Instance details

Defined in Data.Geospatial.Internal.GeoFeature

NFData a => NFData (GeoFeature a) Source # 
Instance details

Defined in Data.Geospatial.Internal.GeoFeature

Methods

rnf :: GeoFeature a -> () #

type Rep (GeoFeature a) Source # 
Instance details

Defined in Data.Geospatial.Internal.GeoFeature

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

properties :: forall a a. Lens (GeoFeature a) (GeoFeature a) a a Source #

Prisms

BasicTypes

Geometry

CRS