geojson-2.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 GeoPositionWithoutCRS Source #

Instances

Eq GeoPositionWithoutCRS Source # 
Show GeoPositionWithoutCRS Source # 
Generic GeoPositionWithoutCRS Source # 
ToJSON GeoPositionWithoutCRS Source # 
FromJSON GeoPositionWithoutCRS Source # 
Storable GeoPositionWithoutCRS Source # 
NFData GeoPositionWithoutCRS Source # 

Methods

rnf :: GeoPositionWithoutCRS -> () #

HasGeoPositionWithoutCRS GeoPositionWithoutCRS Source # 
type Rep GeoPositionWithoutCRS Source # 
type Rep GeoPositionWithoutCRS = D1 * (MetaData "GeoPositionWithoutCRS" "Data.Geospatial.Internal.BasicTypes" "geojson-2.0.0-83h4RRWcSVDK020mHmpqKJ" False) ((:+:) * ((:+:) * (C1 * (MetaCons "GeoEmpty" PrefixI False) (U1 *)) (C1 * (MetaCons "GeoPointXY" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PointXY)))) ((:+:) * (C1 * (MetaCons "GeoPointXYZ" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PointXYZ))) (C1 * (MetaCons "GeoPointXYZM" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Show GeoPoint Source # 
Generic GeoPoint Source # 

Associated Types

type Rep GeoPoint :: * -> * #

Methods

from :: GeoPoint -> Rep GeoPoint x #

to :: Rep GeoPoint x -> GeoPoint #

ToJSON GeoPoint Source # 
FromJSON GeoPoint Source # 
NFData GeoPoint Source # 

Methods

rnf :: GeoPoint -> () #

type Rep GeoPoint Source # 
type Rep GeoPoint = D1 * (MetaData "GeoPoint" "Data.Geospatial.Internal.Geometry.GeoPoint" "geojson-2.0.0-83h4RRWcSVDK020mHmpqKJ" True) (C1 * (MetaCons "GeoPoint" PrefixI True) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Show PointXY Source # 
Generic PointXY Source # 

Associated Types

type Rep PointXY :: * -> * #

Methods

from :: PointXY -> Rep PointXY x #

to :: Rep PointXY x -> PointXY #

Storable PointXY Source # 
NFData PointXY Source # 

Methods

rnf :: PointXY -> () #

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

data PointXYZ Source #

Constructors

PointXYZ 

Fields

Instances

Eq PointXYZ Source # 
Show PointXYZ Source # 
Generic PointXYZ Source # 

Associated Types

type Rep PointXYZ :: * -> * #

Methods

from :: PointXYZ -> Rep PointXYZ x #

to :: Rep PointXYZ x -> PointXYZ #

NFData PointXYZ Source # 

Methods

rnf :: PointXYZ -> () #

type Rep PointXYZ Source # 
type Rep PointXYZ = D1 * (MetaData "PointXYZ" "Data.Geospatial.Internal.BasicTypes" "geojson-2.0.0-83h4RRWcSVDK020mHmpqKJ" False) (C1 * (MetaCons "PointXYZ" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_xyzX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) ((:*:) * (S1 * (MetaSel (Just Symbol "_xyzY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)) (S1 * (MetaSel (Just Symbol "_xyzZ") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Double)))))

data PointXYZM Source #

Constructors

PointXYZM 

Fields

splitGeoMultiPoint :: GeoMultiPoint -> Vector GeoPoint Source #

Split GeoMultiPoint coordinates into multiple GeoPoints

mergeGeoPoints :: Vector GeoPoint -> GeoMultiPoint Source #

Merge multiple GeoPoints into one GeoMultiPoint

splitGeoMultiPolygon :: GeoMultiPolygon -> Vector GeoPolygon Source #

Split GeoMultiPolygon coordinates into multiple GeoPolygons

mergeGeoPolygons :: Vector GeoPolygon -> GeoMultiPolygon Source #

Merge multiple GeoPolygons into one GeoMultiPolygon

newtype GeoLine Source #

Instances

Eq GeoLine Source # 

Methods

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

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

Show GeoLine Source # 
Generic GeoLine Source # 

Associated Types

type Rep GeoLine :: * -> * #

Methods

from :: GeoLine -> Rep GeoLine x #

to :: Rep GeoLine x -> GeoLine #

ToJSON GeoLine Source # 
FromJSON GeoLine Source # 
NFData GeoLine Source # 

Methods

rnf :: GeoLine -> () #

type Rep GeoLine Source # 
type Rep GeoLine = D1 * (MetaData "GeoLine" "Data.Geospatial.Internal.Geometry.GeoLine" "geojson-2.0.0-83h4RRWcSVDK020mHmpqKJ" True) (C1 * (MetaCons "GeoLine" PrefixI True) (S1 * (MetaSel (Just Symbol "_unGeoLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (LineString GeoPositionWithoutCRS))))

splitGeoMultiLine :: GeoMultiLine -> Vector GeoLine Source #

Split GeoMultiLine coordinates into multiple GeoLines

mergeGeoLines :: Vector 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 # 
Show GeospatialGeometry Source # 
Generic GeospatialGeometry Source # 
ToJSON GeospatialGeometry Source #

encodes Geometry Objects to GeoJSON

FromJSON GeospatialGeometry Source #

decodes Geometry Objects from GeoJSON

Aeson doesnt decode "null" into Null unfortunately

NFData GeospatialGeometry Source # 

Methods

rnf :: GeospatialGeometry -> () #

type Rep GeospatialGeometry Source # 

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 # 
Show CRSObject Source # 
ToJSON CRSObject Source #

encode CRS Objects to GeoJSON

FromJSON CRSObject Source #

decode CRS Objects from GeoJSON

Aeson doesnt decode "null" to Null unfortunately

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.

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 # 

Methods

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

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

Show a => Show (GeoFeature a) Source # 
Generic (GeoFeature a) Source # 

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

FromJSON a => FromJSON (GeoFeature a) Source #

Decodes Feature objects from GeoJSON

NFData a => NFData (GeoFeature a) Source # 

Methods

rnf :: GeoFeature a -> () #

type Rep (GeoFeature a) Source # 

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