vectortiles-1.0.0: GIS Vector Tiles, as defined by Mapbox.

Copyright(c) Azavea, 2016
LicenseApache 2
MaintainerColin Woodbury <cwoodbury@azavea.com>
Safe HaskellNone
LanguageHaskell2010

Geography.VectorTile.Geometry

Contents

Description

 

Synopsis

Geometries

Types

class Geometry g where Source #

Any classical type considered a GIS "geometry". These must be able to convert between an encodable list of Commands.

Minimal complete definition

fromCommands, toCommands

Instances

Geometry Polygon Source #

A valid Feature of polygons must contain at least one sequence of:

An Exterior Ring, followed by 0 or more Interior Rings.

Any Ring must have a MoveTo with a count of 1, a single LineTo with a count of at least 2, and a single ClosePath command.

Performs no sanity checks for malformed Interior Rings.

Geometry LineString Source #

A valid Feature of linestrings must contain pairs of:

A MoveTo with a count of 1, followed by one LineTo command with a count greater than 0.

Geometry Point Source #

A valid Feature of points must contain a single MoveTo command with a count greater than 0.

type Point = (Int, Int) Source #

Points in space. Using "Record Pattern Synonyms" here allows us to treat Point like a normal ADT, while its implementation remains an unboxed (Int,Int).

newtype LineString Source #

newtype compiles away to expose only the Vector of unboxed Points at runtime.

Constructors

LineString 

Fields

Instances

Eq LineString Source # 
Show LineString Source # 
Generic LineString Source # 

Associated Types

type Rep LineString :: * -> * #

NFData LineString Source # 

Methods

rnf :: LineString -> () #

Geometry LineString Source #

A valid Feature of linestrings must contain pairs of:

A MoveTo with a count of 1, followed by one LineTo command with a count greater than 0.

Geom LineString Source # 
type Rep LineString Source # 
type Rep LineString = D1 (MetaData "LineString" "Geography.VectorTile.Geometry" "vectortiles-1.0.0-9253U2nfEGPHQq8Yl4euFw" True) (C1 (MetaCons "LineString" PrefixI True) (S1 (MetaSel (Just Symbol "lsPoints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Point))))

data Polygon Source #

A polygon aware of its interior rings.

Constructors

Polygon 

Instances

Eq Polygon Source # 

Methods

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

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

Show Polygon Source # 
Generic Polygon Source # 

Associated Types

type Rep Polygon :: * -> * #

Methods

from :: Polygon -> Rep Polygon x #

to :: Rep Polygon x -> Polygon #

NFData Polygon Source # 

Methods

rnf :: Polygon -> () #

Geometry Polygon Source #

A valid Feature of polygons must contain at least one sequence of:

An Exterior Ring, followed by 0 or more Interior Rings.

Any Ring must have a MoveTo with a count of 1, a single LineTo with a count of at least 2, and a single ClosePath command.

Performs no sanity checks for malformed Interior Rings.

Geom Polygon Source # 
type Rep Polygon Source # 
type Rep Polygon = D1 (MetaData "Polygon" "Geography.VectorTile.Geometry" "vectortiles-1.0.0-9253U2nfEGPHQq8Yl4euFw" False) (C1 (MetaCons "Polygon" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "polyPoints") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector Point))) (S1 (MetaSel (Just Symbol "inner") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector Polygon)))))

Operations

area :: Polygon -> Float Source #

The area of a Polygon is the difference between the areas of its outer ring and inner rings.

surveyor :: Vector Point -> Float Source #

The surveyor's formula for calculating the area of a Polygon. If the value reported here is negative, then the Polygon should be considered an Interior Ring.

Assumption: The Vector given has at least 4 Points.

distance :: Point -> Point -> Float Source #

Euclidean distance.

Commands

data Command Source #

The possible commands, and the values they hold.

Constructors

MoveTo (Vector (Int, Int)) 
LineTo (Vector (Int, Int)) 
ClosePath 

commands :: [Word32] -> Either Text [Command] Source #

Attempt to parse a list of Command/Parameter integers, as defined here:

https://github.com/mapbox/vector-tile-spec/tree/master/2.1#43-geometry-encoding

uncommands :: [Command] -> [Word32] Source #

Convert a list of parsed Commands back into their original Command and Z-encoded Parameter integer forms.

Z-Encoding

zig :: Int -> Word32 Source #

Z-encode a 64-bit Int.

unzig :: Word32 -> Int Source #

Decode a Z-encoded Word32 into a 64-bit Int.

Orphan instances

Monoid Point Source #

Points are just vectors in R2, and thus form a Vector space.

Methods

mempty :: Point #

mappend :: Point -> Point -> Point #

mconcat :: [Point] -> Point #