geojson-4.0.1: 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.Internal.BasicTypes

Contents

Description

Basic types for GeoJSON representations.

Synopsis

Coordinate types

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.1-8KaGhZSuZscBxKMdGBsGB5" 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 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.1-8KaGhZSuZscBxKMdGBsGB5" 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.1-8KaGhZSuZscBxKMdGBsGB5" 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.1-8KaGhZSuZscBxKMdGBsGB5" 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 DoubleArray Source #

Constructors

DoubleArray [Double] 
Instances
Eq DoubleArray Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Show DoubleArray Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Generic DoubleArray Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Associated Types

type Rep DoubleArray :: * -> * #

ToJSON DoubleArray Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

FromJSON DoubleArray Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

NFData DoubleArray Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

Methods

rnf :: DoubleArray -> () #

type Rep DoubleArray Source # 
Instance details

Defined in Data.Geospatial.Internal.BasicTypes

type Rep DoubleArray = D1 (MetaData "DoubleArray" "Data.Geospatial.Internal.BasicTypes" "geojson-4.0.1-8KaGhZSuZscBxKMdGBsGB5" True) (C1 (MetaCons "DoubleArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Double])))

CRS Reference types

type Name = Text Source #

type Code = Int Source #

type Href = Text Source #

Feature Types

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 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.1-8KaGhZSuZscBxKMdGBsGB5" 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)))