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

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

Geography.VectorTile.VectorTile

Contents

Description

High-level types for representing Vector Tiles.

Synopsis

Types

newtype VectorTile Source #

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

Constructors

VectorTile 

Fields

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 # 

Methods

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

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

Show Layer Source # 

Methods

showsPrec :: Int -> Layer -> ShowS #

show :: Layer -> String #

showList :: [Layer] -> ShowS #

Generic Layer Source # 

Associated Types

type Rep Layer :: * -> * #

Methods

from :: Layer -> Rep Layer x #

to :: Rep Layer x -> Layer #

NFData Layer Source # 

Methods

rnf :: Layer -> () #

Protobuffable Layer Source # 
type Rep Layer Source # 
type Protobuf Layer Source # 

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.VectorTile" "vectortiles-1.2.0.6-GhKhvkmaJVwEvf0AuwOrth" False) (C1 (MetaCons "Feature" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_featureId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "_metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text Val))) (S1 (MetaSel (Just Symbol "_geometries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Vector g))))))

data Val Source #

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

Instances

Eq Val Source # 

Methods

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

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

Ord Val Source # 

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 # 

Methods

showsPrec :: Int -> Val -> ShowS #

show :: Val -> String #

showList :: [Val] -> ShowS #

Generic Val Source # 

Associated Types

type Rep Val :: * -> * #

Methods

from :: Val -> Rep Val x #

to :: Rep Val x -> Val #

NFData Val Source # 

Methods

rnf :: Val -> () #

Protobuffable Val Source # 
type Rep Val Source # 
type Protobuf Val Source # 

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 => (Map Text Layer -> f (Map Text Layer)) -> VectorTile -> f VectorTile Source #

Lens' VectorTile (Map Text Layer)

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

Lens' Layer Int

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

Lens' Layer Text

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

Lens' Layer (Vector (Feature Point))

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

Lens' Layer (Vector (Feature LineString)))

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

Lens' Layer (Vector (Feature Polygon)))

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

Lens' Layer Int

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

Lens' (Feature g) Int

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

Lens' (Feature g) (Map Text Val)

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

Lens' (Feature g) (Vector g)