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

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.

The order in which to explore the modules of this library is as follows:

  1. Geography.VectorTile (here)
  2. Geography.VectorTile.Geometry
  3. Geography.VectorTile.Raw

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
import qualified Geography.VectorTile.Raw as R

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

Or encode a VectorTile back into a ByteString:

roadsBytes :: VectorTile -> BS.ByteString
roadsBytes = R.encode . untile

Synopsis

Types

newtype VectorTile Source #

A high-level representation of a Vector Tile. At its simplest, a tile is just a list of Layers.

There is potential to implement _layers as a Map, with its String-based name as a key.

Constructors

VectorTile 

Fields

Instances

Eq VectorTile Source # 
Show VectorTile Source # 
Generic VectorTile Source # 

Associated Types

type Rep VectorTile :: * -> * #

NFData VectorTile Source # 

Methods

rnf :: VectorTile -> () #

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

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

data Feature g 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.

Constructors

Feature 

Fields

Instances

Eq g => Eq (Feature g) Source # 

Methods

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

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

Show g => Show (Feature g) Source # 

Methods

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

show :: Feature g -> String #

showList :: [Feature g] -> ShowS #

Generic (Feature g) Source # 

Associated Types

type Rep (Feature g) :: * -> * #

Methods

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

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

NFData g => NFData (Feature g) Source # 

Methods

rnf :: Feature g -> () #

type Rep (Feature g) Source # 
type Rep (Feature g) = D1 (MetaData "Feature" "Geography.VectorTile" "vectortiles-1.0.0-9253U2nfEGPHQq8Yl4euFw" False) (C1 (MetaCons "Feature" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_featureId") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "_metadata") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Map Text Val))) (S1 (MetaSel (Just Symbol "_geometries") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector g))))))

data Val Source #

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

Protobuf Conversions

From Protobuf

Generally the tile function is the only one needed here. Usage:

import qualified Geography.VectorTile.Raw as R

R.decode someBytes >>= tile

Note that since the Data.ProtocolBuffers library does not handle default values, we handle those specifically defined in vector_tile.proto explicitely here. See:

https://github.com/mapbox/vector-tile-spec/blob/master/2.1/vector_tile.proto

tile :: RawVectorTile -> Either Text VectorTile Source #

Convert a RawVectorTile of parsed protobuf data into a useable VectorTile.

layer :: RawLayer -> Either Text Layer Source #

Convert a single RawLayer of parsed protobuf data into a useable Layer.

features :: [Text] -> [RawVal] -> [RawFeature] -> Either Text (Vector (Feature Point), Vector (Feature LineString), Vector (Feature Polygon)) Source #

Convert a list of RawFeatures of parsed protobuf data into Vectors of each of the three legal Geometry types.

The long type signature is due to two things:

  1. Features are polymorphic at the high level, but not at the parsed protobuf mid-level. In a [RawFeature], there are features of points, linestrings, and polygons all mixed together.
  2. RawLayers and RawFeatures are strongly coupled at the protobuf level. In order to achieve higher compression ratios, RawLayers contain all metadata in key/value lists to be shared across their RawFeatures, while those RawFeatures store only indices into those lists. As a result, this function needs to be passed those key/value lists from the parent RawLayer, and a more isomorphic:
feature :: Geometry g => RawFeature -> Either Text (Feature g)

is not possible.

value :: RawVal -> Either Text Val Source #

Convert a RawVal parsed from protobuf data into a useable Val. The higher-level Val type better expresses the mutual exclusivity of the Value types.

To Protobuf

To convert from high-level data back into a form that can be encoded into raw protobuf bytes, use:

import qualified Geography.VectorTile.Raw as R

R.encode $ untile someTile

This is a pure process and will succeed every time.

untile :: VectorTile -> RawVectorTile Source #

Encode a high-level VectorTile back into its mid-level RawVectorTile form.

unlayer :: Layer -> RawLayer Source #

Encode a high-level Layer back into its mid-level RawLayer form.

unfeature :: Geom g => [Text] -> [Val] -> Feature g -> RawFeature Source #

Encode a high-level Feature back into its mid-level RawFeature form.

unval :: Val -> RawVal Source #

Encode a high-level Val back into its mid-level RawVal form.

Lenses

This section can be safely ignored if one isn't concerned with lenses. Otherwise, see the following for a good primer on Haskell lenses: http://hackage.haskell.org/package/lens-tutorial-1.0.1/docs/Control-Lens-Tutorial.html

These lenses are written in a generic way to avoid taking a dependency on one of the lens libraries.

layers :: Functor f => (Vector Layer -> f (Vector Layer)) -> VectorTile -> f VectorTile Source #

Lens' VectorTile (Vector Layer)

version :: Functor f => (Layer -> f Int) -> Layer -> f Layer Source #

Lens' Layer Int

name :: Functor f => (Layer -> f Text) -> Layer -> f Layer Source #

Lens' Layer Text

points :: Functor f => (Layer -> f (Vector (Feature Point))) -> Layer -> f Layer Source #

Lens' Layer (Vector (Feature Point))

linestrings :: Functor f => (Layer -> f (Vector (Feature LineString))) -> Layer -> f Layer Source #

Lens' Layer (Vector (Feature LineString)))

polygons :: Functor f => (Layer -> f (Vector (Feature Polygon))) -> Layer -> f Layer Source #

Lens' Layer (Vector (Feature Polygon)))

extent :: Functor f => (Layer -> f Int) -> Layer -> f Layer Source #

Lens' Layer Int

featureId :: Functor f => (Feature g -> f Int) -> Feature g -> f (Feature g) Source #

Lens' (Feature g) Int

metadata :: Functor f => (Feature g -> f (Map Text Val)) -> Feature g -> f (Feature g) Source #

Lens' (Feature g) (Map Text Val)

geometries :: Functor f => (Feature g -> f (Vector g)) -> Feature g -> f (Feature g) Source #

Lens' (Feature g) (Vector g)