| Copyright | (c) Colin Woodbury 2016 - 2018 |
|---|---|
| License | BSD3 |
| Maintainer | Colin Woodbury <colingw@gmail.com> |
| Safe Haskell | None |
| Language | Haskell2010 |
Geography.VectorTile.Internal
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 for the user-friendly version.
- type family Protobuf a = pb | pb -> a
- class Protobuffable a where
- class ProtobufGeom g where
- data Tile = Tile !(Seq Layer) !ExtField
- data Layer = Layer !Word32 !Utf8 !(Seq Feature) !(Seq Utf8) !(Seq Value) !(Maybe Word32) !ExtField
- data Feature = Feature {}
- data Value = Value {
- string_value :: !(Maybe Utf8)
- float_value :: !(Maybe Float)
- double_value :: !(Maybe Double)
- int_value :: !(Maybe Int64)
- uint_value :: !(Maybe Word64)
- sint_value :: !(Maybe Int64)
- bool_value :: !(Maybe Bool)
- ext'field :: !ExtField
- data GeomType
- = UNKNOWN
- | POINT
- | LINESTRING
- | POLYGON
- data Command
- commands :: [Word32] -> [Command]
- uncommands :: [Command] -> Seq Word32
- zig :: Int -> Word32
- unzig :: Word32 -> Int
- feats :: Seq ByteString -> Seq Value -> Seq Feature -> Either Text Feats
- unfeats :: ProtobufGeom g => HashMap ByteString Int -> HashMap Val Int -> GeomType -> Feature (GeomVec g) -> Feature
Types
Protobuf Conversion
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
Instances
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
Methods
fromCommands :: [Command] -> Either Text (GeomVec g) Source #
toCommands :: GeomVec g -> [Command] Source #
Instances
| ProtobufGeom Polygon Source # | A valid An Exterior Ring, followed by 0 or more Interior Rings. Any Ring must have a Performs no sanity checks for malformed Interior Rings. |
| ProtobufGeom LineString Source # | A valid A |
| ProtobufGeom Point Source # | A valid |
Decoded Middle-Types
Instances
| Eq Tile Source # | |
| Data Tile Source # | |
| Ord Tile Source # | |
| Show Tile Source # | |
| Generic Tile Source # | |
| ExtendMessage Tile Source # | |
| GPB Tile Source # | |
| Wire Tile Source # | |
| TextMsg Tile Source # | |
| TextType Tile Source # | |
| ReflectDescriptor Tile Source # | |
| Mergeable Tile Source # | |
| Default Tile Source # | |
| MessageAPI msg' (msg' -> Tile) Tile Source # | |
| type Rep Tile Source # | |
Instances
| Eq Layer Source # | |
| Data Layer Source # | |
| Ord Layer Source # | |
| Show Layer Source # | |
| Generic Layer Source # | |
| ExtendMessage Layer Source # | |
| GPB Layer Source # | |
| Wire Layer Source # | |
| TextMsg Layer Source # | |
| TextType Layer Source # | |
| ReflectDescriptor Layer Source # | |
| Mergeable Layer Source # | |
| Default Layer Source # | |
| MessageAPI msg' (msg' -> Layer) Layer Source # | |
| type Rep Layer Source # | |
Constructors
| Feature | |
Instances
| Eq Feature Source # | |
| Data Feature Source # | |
| Ord Feature Source # | |
| Show Feature Source # | |
| Generic Feature Source # | |
| GPB Feature Source # | |
| Wire Feature Source # | |
| TextMsg Feature Source # | |
| TextType Feature Source # | |
| ReflectDescriptor Feature Source # | |
| Mergeable Feature Source # | |
| Default Feature Source # | |
| MessageAPI msg' (msg' -> Feature) Feature Source # | |
| type Rep Feature Source # | |
Constructors
| Value | |
Fields
| |
Instances
| Eq Value Source # | |
| Data Value Source # | |
| Ord Value Source # | |
| Show Value Source # | |
| Generic Value Source # | |
| ExtendMessage Value Source # | |
| GPB Value Source # | |
| Wire Value Source # | |
| TextMsg Value Source # | |
| TextType Value Source # | |
| ReflectDescriptor Value Source # | |
| Mergeable Value Source # | |
| Default Value Source # | |
| MessageAPI msg' (msg' -> Value) Value Source # | |
| type Rep Value Source # | |
Constructors
| UNKNOWN | |
| POINT | |
| LINESTRING | |
| POLYGON |
Instances
Commands
The possible commands, and the values they hold.
commands :: [Word32] -> [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] -> Seq Word32 Source #
Convert a list of parsed Commands back into their original Command
and Z-encoded Parameter integer forms.
Z-Encoding
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.
feats :: Seq ByteString -> Seq Value -> Seq Feature -> Either Text Feats 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:
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.RawLayers andRawFeatures 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 theirRawFeatures, while thoseRawFeatures store only indices into those lists. As a result, this function needs to be passed those key/value lists from the parentRawLayer, and a more isomorphic:
feature :: ProtobufGeom g => RawFeature -> Either Text (Feature g)
is not possible.