| Copyright | (c) Colin Woodbury 2016 - 2020 |
|---|---|
| License | BSD3 |
| Maintainer | Colin Woodbury <colin@fosskers.ca> |
| 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.
Synopsis
- type family Protobuf a = pb | pb -> a
- class Protobuffable a where
- fromProtobuf :: Protobuf a -> Either Text a
- toProtobuf :: a -> Protobuf a
- class ProtobufGeom g where
- fromCommands :: [Command] -> Either Text (GeomVec g)
- toCommands :: GeomVec g -> [Command]
- 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.
Instances
| type Protobuf Val Source # | |
Defined in Geography.VectorTile.Internal | |
| type Protobuf Layer Source # | |
Defined in Geography.VectorTile.Internal | |
| type Protobuf VectorTile Source # | |
Defined in Geography.VectorTile.Internal | |
class Protobuffable a where Source #
A type which can be converted to and from an underlying Protobuf type,
according to the Protobuf type family.
Instances
| Protobuffable Val Source # | |
Defined in Geography.VectorTile.Internal | |
| Protobuffable Layer Source # | |
Defined in Geography.VectorTile.Internal | |
| Protobuffable VectorTile Source # | |
Defined in Geography.VectorTile.Internal Methods fromProtobuf :: Protobuf VectorTile -> Either Text VectorTile Source # | |
class ProtobufGeom g where Source #
Any classical type considered a GIS "geometry". These must be able
to convert between an encodable list of Commands.
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. |
Defined in Geography.VectorTile.Internal | |
| ProtobufGeom LineString Source # | A valid A |
Defined in Geography.VectorTile.Internal Methods fromCommands :: [Command] -> Either Text (GeomVec LineString) Source # toCommands :: GeomVec LineString -> [Command] Source # | |
| ProtobufGeom Point Source # | A valid |
Defined in Geography.VectorTile.Internal | |
Decoded Middle-Types
Instances
Instances
Constructors
| Feature | |
Instances
Constructors
| Value | |
Fields
| |
Instances
Constructors
| UNKNOWN | |
| POINT | |
| LINESTRING | |
| POLYGON |
Instances
Commands
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.