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

Copyright(c) Colin Woodbury 2016 - 2020
LicenseBSD3
MaintainerColin Woodbury <colin@fosskers.ca>
Safe HaskellNone
LanguageHaskell2010

Geography.VectorTile

Contents

Description

GIS Vector Tiles, as defined by Mapbox.

This library implements version 2.1 of the official Mapbox spec, as defined here: https://github.com/mapbox/vector-tile-spec/tree/master/2.1

Note that currently this library ignores top-level protobuf extensions, Value extensions, and UNKNOWN geometries.

Usage

This library reads and writes strict ByteStrings. Given some legal VectorTile file called roads.mvt:

import qualified Data.ByteString as BS
import           Data.Text (Text)
import           Geography.VectorTile

-- | Read in raw protobuf data and decode it into a high-level type.
roads :: IO (Either Text VectorTile)
roads = tile <$> BS.readFile "roads.mvt"

Likewise, use the untile function to convert a VectorTile back into a ByteString.

Synopsis

Vector Tiles

newtype VectorTile Source #

A high-level representation of a Vector Tile. Implemented internally as a HashMap, so that access to individual layers can be fast if you know the layer names ahead of time.

The layer name itself, a lazy ByteString, is guaranteed to be UTF-8. If you wish to convert it to Text, consider decodeUtf8.

Constructors

VectorTile 
Instances
Eq VectorTile Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Show VectorTile Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Generic VectorTile Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Associated Types

type Rep VectorTile :: Type -> Type #

NFData VectorTile Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

rnf :: VectorTile -> () #

Protobuffable VectorTile Source # 
Instance details

Defined in Geography.VectorTile.Internal

type Rep VectorTile Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

type Rep VectorTile = D1 (MetaData "VectorTile" "Geography.VectorTile.VectorTile" "vectortiles-1.5.1-7MnYiWGlVzVJYfj7ka9AnU" True) (C1 (MetaCons "VectorTile" PrefixI True) (S1 (MetaSel (Just "_layers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap ByteString Layer))))
type Protobuf VectorTile Source # 
Instance details

Defined in Geography.VectorTile.Internal

tile :: ByteString -> Either Text VectorTile Source #

Attempt to parse a VectorTile from a strict collection of bytes.

untile :: VectorTile -> ByteString Source #

Convert a VectorTile back into bytes.

type Lens' s a = forall f. Functor f => (a -> f a) -> s -> f s Source #

Simple Lenses compatible with both lens and microlens.

data Layer Source #

A layer, which could contain any number of Features of any Geometry type. This codec only respects the canonical three Geometry types, and we split them here explicitely to allow for more fine-grained access to each type.

Constructors

Layer 

Fields

Instances
Eq Layer Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

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

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

Show Layer Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

showsPrec :: Int -> Layer -> ShowS #

show :: Layer -> String #

showList :: [Layer] -> ShowS #

Generic Layer Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Associated Types

type Rep Layer :: Type -> Type #

Methods

from :: Layer -> Rep Layer x #

to :: Rep Layer x -> Layer #

NFData Layer Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

rnf :: Layer -> () #

Protobuffable Layer Source # 
Instance details

Defined in Geography.VectorTile.Internal

type Rep Layer Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

type Protobuf Layer Source # 
Instance details

Defined in Geography.VectorTile.Internal

data Feature gs Source #

A geographic feature. Features are a set of geometries that share some common theme:

  • Points: schools, gas station locations, etc.
  • LineStrings: Roads, power lines, rivers, etc.
  • Polygons: Buildings, water bodies, etc.

Where, for instance, all school locations may be stored as a single Feature, and no Point within that Feature would represent anything else.

Note: Each Geometry type and their Multi* counterpart are considered the same thing, as a Vector of that Geometry.

Note: The keys to the metadata are ByteString, but are guaranteed to be UTF-8.

Constructors

Feature 

Fields

Instances
Eq gs => Eq (Feature gs) Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

(==) :: Feature gs -> Feature gs -> Bool #

(/=) :: Feature gs -> Feature gs -> Bool #

Show gs => Show (Feature gs) Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

showsPrec :: Int -> Feature gs -> ShowS #

show :: Feature gs -> String #

showList :: [Feature gs] -> ShowS #

Generic (Feature gs) Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Associated Types

type Rep (Feature gs) :: Type -> Type #

Methods

from :: Feature gs -> Rep (Feature gs) x #

to :: Rep (Feature gs) x -> Feature gs #

NFData gs => NFData (Feature gs) Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

rnf :: Feature gs -> () #

type Rep (Feature gs) Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

type Rep (Feature gs) = D1 (MetaData "Feature" "Geography.VectorTile.VectorTile" "vectortiles-1.5.1-7MnYiWGlVzVJYfj7ka9AnU" False) (C1 (MetaCons "Feature" PrefixI True) (S1 (MetaSel (Just "_featureId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word) :*: (S1 (MetaSel (Just "_metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap ByteString Val)) :*: S1 (MetaSel (Just "_geometries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 gs))))

data Val Source #

Legal Metadata Value types. Note that S64 are Z-encoded automatically by the underlying Text.ProtocolBuffers library.

Instances
Eq Val Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

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

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

Ord Val Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

compare :: Val -> Val -> Ordering #

(<) :: Val -> Val -> Bool #

(<=) :: Val -> Val -> Bool #

(>) :: Val -> Val -> Bool #

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

max :: Val -> Val -> Val #

min :: Val -> Val -> Val #

Show Val Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

showsPrec :: Int -> Val -> ShowS #

show :: Val -> String #

showList :: [Val] -> ShowS #

Generic Val Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Associated Types

type Rep Val :: Type -> Type #

Methods

from :: Val -> Rep Val x #

to :: Rep Val x -> Val #

Hashable Val Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

hashWithSalt :: Int -> Val -> Int #

hash :: Val -> Int #

NFData Val Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

Methods

rnf :: Val -> () #

Protobuffable Val Source # 
Instance details

Defined in Geography.VectorTile.Internal

type Rep Val Source # 
Instance details

Defined in Geography.VectorTile.VectorTile

type Protobuf Val Source # 
Instance details

Defined in Geography.VectorTile.Internal

Geometries

data Point Source #

A strict pair of integers indicating some location on a discrete grid. Point 0 0 is the top-left.

Constructors

Point 

Fields

Instances
Eq Point Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Methods

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

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

Show Point Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Generic Point Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Associated Types

type Rep Point :: Type -> Type #

Methods

from :: Point -> Rep Point x #

to :: Rep Point x -> Point #

Semigroup Point Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Methods

(<>) :: Point -> Point -> Point #

sconcat :: NonEmpty Point -> Point #

stimes :: Integral b => b -> Point -> Point #

Monoid Point Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Methods

mempty :: Point #

mappend :: Point -> Point -> Point #

mconcat :: [Point] -> Point #

Storable Point Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Methods

sizeOf :: Point -> Int #

alignment :: Point -> Int #

peekElemOff :: Ptr Point -> Int -> IO Point #

pokeElemOff :: Ptr Point -> Int -> Point -> IO () #

peekByteOff :: Ptr b -> Int -> IO Point #

pokeByteOff :: Ptr b -> Int -> Point -> IO () #

peek :: Ptr Point -> IO Point #

poke :: Ptr Point -> Point -> IO () #

NFData Point Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Methods

rnf :: Point -> () #

ProtobufGeom Point Source #

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

Instance details

Defined in Geography.VectorTile.Internal

Methods

fromCommands :: [Command] -> Either Text (GeomVec Point) Source #

toCommands :: GeomVec Point -> [Command] Source #

type Rep Point Source # 
Instance details

Defined in Geography.VectorTile.Geometry

type Rep Point = D1 (MetaData "Point" "Geography.VectorTile.Geometry" "vectortiles-1.5.1-7MnYiWGlVzVJYfj7ka9AnU" False) (C1 (MetaCons "Point" PrefixI True) (S1 (MetaSel (Just "x") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "y") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))

newtype LineString Source #

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

Constructors

LineString 

Fields

Instances
Eq LineString Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Show LineString Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Generic LineString Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Associated Types

type Rep LineString :: Type -> Type #

NFData LineString Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Methods

rnf :: LineString -> () #

ProtobufGeom LineString Source #

A valid RawFeature of linestrings must contain pairs of:

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

Instance details

Defined in Geography.VectorTile.Internal

type Rep LineString Source # 
Instance details

Defined in Geography.VectorTile.Geometry

type Rep LineString = D1 (MetaData "LineString" "Geography.VectorTile.Geometry" "vectortiles-1.5.1-7MnYiWGlVzVJYfj7ka9AnU" True) (C1 (MetaCons "LineString" PrefixI True) (S1 (MetaSel (Just "lsPoints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector Point))))

data Polygon Source #

A polygon aware of its interior rings.

VectorTiles require that Polygon exteriors have clockwise winding order, and that interior holes have counter-clockwise winding order. These assume that the origin (0,0) is in the *top-left* corner.

Constructors

Polygon 

Fields

Instances
Eq Polygon Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Methods

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

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

Show Polygon Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Generic Polygon Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Associated Types

type Rep Polygon :: Type -> Type #

Methods

from :: Polygon -> Rep Polygon x #

to :: Rep Polygon x -> Polygon #

NFData Polygon Source # 
Instance details

Defined in Geography.VectorTile.Geometry

Methods

rnf :: Polygon -> () #

ProtobufGeom Polygon Source #

A valid RawFeature 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.

Instance details

Defined in Geography.VectorTile.Internal

Methods

fromCommands :: [Command] -> Either Text (GeomVec Polygon) Source #

toCommands :: GeomVec Polygon -> [Command] Source #

type Rep Polygon Source # 
Instance details

Defined in Geography.VectorTile.Geometry

type Rep Polygon = D1 (MetaData "Polygon" "Geography.VectorTile.Geometry" "vectortiles-1.5.1-7MnYiWGlVzVJYfj7ka9AnU" False) (C1 (MetaCons "Polygon" PrefixI True) (S1 (MetaSel (Just "polyPoints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector Point)) :*: S1 (MetaSel (Just "inner") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector Polygon))))

area :: Polygon -> Double Source #

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

surveyor :: Vector Point -> Double 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.