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

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

Geography.VectorTile.Protobuf.Internal

Contents

Description

Raw Vector Tile data is stored as binary protobuf data. This module reads and writes raw protobuf ByteStrings between a data type which closely matches the current Mapbox vector tile spec defined here: https://github.com/mapbox/vector-tile-spec/blob/master/2.1/vector_tile.proto

As this raw version of the data is hard to work with, in practice we convert to a more canonical Haskell type for further processing. See Geography.VectorTile.VectorTile for the user-friendly version.

Please import this module qualified to avoid namespace clashes:

import qualified Geography.VectorTile.Protobuf.Internal as PB

Synopsis

Types

type family Protobuf a = pb | pb -> a Source #

A family of data types which can associated with concrete underlying Protobuf types.

class Protobuffable a where Source #

A type which can be converted to and from an underlying Protobuf type, according to the Protobuf type family.

Minimal complete definition

fromProtobuf, toProtobuf

class ProtobufGeom 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

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.

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.

ProtobufGeom Point Source #

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

data RawLayer Source #

Contains a pseudo-map of metadata, to be shared across all RawFeatures of this RawLayer.

Instances

Eq RawLayer Source # 
Show RawLayer Source # 
Generic RawLayer Source # 

Associated Types

type Rep RawLayer :: * -> * #

Methods

from :: RawLayer -> Rep RawLayer x #

to :: Rep RawLayer x -> RawLayer #

NFData RawLayer Source # 

Methods

rnf :: RawLayer -> () #

Decode RawLayer Source # 
Encode RawLayer Source # 

Methods

encode :: RawLayer -> Put #

type Rep RawLayer Source # 

data RawVal Source #

The Value types of metadata fields.

Instances

Eq RawVal Source # 

Methods

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

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

Show RawVal Source # 
Generic RawVal Source # 

Associated Types

type Rep RawVal :: * -> * #

Methods

from :: RawVal -> Rep RawVal x #

to :: Rep RawVal x -> RawVal #

NFData RawVal Source # 

Methods

rnf :: RawVal -> () #

Decode RawVal Source # 
Encode RawVal Source # 

Methods

encode :: RawVal -> Put #

type Rep RawVal Source # 

data RawFeature Source #

A set of geometries unified by some theme.

data GeomType Source #

The four potential Geometry types. The spec allows for encoders to set Unknown as the type, but our decoder ignores these.

Constructors

Unknown 
Point 
LineString 
Polygon 

Instances

Enum GeomType Source # 
Eq GeomType Source # 
Show GeomType Source # 
Generic GeomType Source # 

Associated Types

type Rep GeomType :: * -> * #

Methods

from :: GeomType -> Rep GeomType x #

to :: Rep GeomType x -> GeomType #

NFData GeomType Source # 

Methods

rnf :: GeomType -> () #

Decode GeomType Source # 
Encode GeomType Source # 

Methods

encode :: GeomType -> Put #

type Rep GeomType Source # 
type Rep GeomType = D1 (MetaData "GeomType" "Geography.VectorTile.Protobuf.Internal" "vectortiles-1.2.0.4-I75cm6FUOxx4tEyZlnmDSl" False) ((:+:) ((:+:) (C1 (MetaCons "Unknown" PrefixI False) U1) (C1 (MetaCons "Point" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LineString" PrefixI False) U1) (C1 (MetaCons "Polygon" PrefixI False) U1)))

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.

Protobuf Conversions

Due to Protobuf Layers and Features having their data coupled, we can't define a Protobuffable instance for Features, and instead must use the two functions below.

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 ProtobufGeom 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 :: ProtobufGeom g => RawFeature -> Either Text (Feature g)

is not possible.

unfeature :: ProtobufGeom g => Map Text Int -> Map Val Int -> GeomType -> Feature g -> RawFeature Source #

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