mbtiles-0.6.0.0: Haskell MBTiles client.

Copyright(c) Joe Canero 2017
LicenseBSD3
Maintainerjmc41493@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Database.Mbtiles

Contents

Description

This module provides support for reading, writing, and updating an mbtiles database, as well as reading metadata from the database.

There is also support for creating a pool of connections to an mbtiles database and streaming tiles.

See the associated README.md for basic usage examples.

Synopsis

Types

data MbtilesT m a Source #

MbtilesT monad that will run actions on an MBTiles file.

Instances

MonadTrans MbtilesT Source # 

Methods

lift :: Monad m => m a -> MbtilesT m a #

Monad m => Monad (MbtilesT m) Source # 

Methods

(>>=) :: MbtilesT m a -> (a -> MbtilesT m b) -> MbtilesT m b #

(>>) :: MbtilesT m a -> MbtilesT m b -> MbtilesT m b #

return :: a -> MbtilesT m a #

fail :: String -> MbtilesT m a #

Functor m => Functor (MbtilesT m) Source # 

Methods

fmap :: (a -> b) -> MbtilesT m a -> MbtilesT m b #

(<$) :: a -> MbtilesT m b -> MbtilesT m a #

Applicative m => Applicative (MbtilesT m) Source # 

Methods

pure :: a -> MbtilesT m a #

(<*>) :: MbtilesT m (a -> b) -> MbtilesT m a -> MbtilesT m b #

(*>) :: MbtilesT m a -> MbtilesT m b -> MbtilesT m b #

(<*) :: MbtilesT m a -> MbtilesT m b -> MbtilesT m a #

MonadIO m => MonadIO (MbtilesT m) Source # 

Methods

liftIO :: IO a -> MbtilesT m a #

type MbtilesIO a = MbtilesT IO a Source #

Type specialization of MbtilesT to IO.

type MbtilesMeta = HashMap Text Text Source #

MBTiles files contain metadata in one of their tables. This is a type alias for a mapping between the metadata key and the metadata value.

data MBTilesError Source #

Data type representing various errors that could occur when opening and validating an MBTiles file.

Constructors

DoesNotExist

The MBTiles file does not exist.

InvalidSchema

The MBTiles schema is invalid according to the spec.

InvalidMetadata

The MBTiles metadata table is invalid.

InvalidTiles

The MBTiles tiles table is invaid.

newtype Z Source #

Newtype wrapper around map zoom level.

Constructors

Z Int 

Instances

ToField Z Source # 

Methods

toField :: Z -> SQLData #

newtype X Source #

Newtype wrapper around a tile's x-coordinate.

Constructors

X Int 

Instances

ToField X Source # 

Methods

toField :: X -> SQLData #

newtype Y Source #

Newtype wrapper around a tile's y-coordinate.

Constructors

Y Int 

Instances

ToField Y Source # 

Methods

toField :: Y -> SQLData #

data Tile a Source #

Data type that represents an entire row from an MBTiles database.

Constructors

Tile 

Fields

Instances

Functor Tile Source # 

Methods

fmap :: (a -> b) -> Tile a -> Tile b #

(<$) :: a -> Tile b -> Tile a #

Eq a => Eq (Tile a) Source # 

Methods

(==) :: Tile a -> Tile a -> Bool #

(/=) :: Tile a -> Tile a -> Bool #

Ord a => Ord (Tile a) Source # 

Methods

compare :: Tile a -> Tile a -> Ordering #

(<) :: Tile a -> Tile a -> Bool #

(<=) :: Tile a -> Tile a -> Bool #

(>) :: Tile a -> Tile a -> Bool #

(>=) :: Tile a -> Tile a -> Bool #

max :: Tile a -> Tile a -> Tile a #

min :: Tile a -> Tile a -> Tile a #

Show a => Show (Tile a) Source # 

Methods

showsPrec :: Int -> Tile a -> ShowS #

show :: Tile a -> String #

showList :: [Tile a] -> ShowS #

FromTile a => FromRow (Tile a) Source # 

Methods

fromRow :: RowParser (Tile a) #

Typeclasses

class ToTile a where Source #

Typeclass representing data types that can be turned into a lazy ByteString and stored as tile data.

Minimal complete definition

toTile

Methods

toTile :: a -> ByteString Source #

class FromTile a where Source #

Typeclass representing data types into which raw tile data can be converted.

Minimal complete definition

fromTile

Methods

fromTile :: ByteString -> a Source #

The MbtilesT monad transformer

runMbtilesT :: MonadIO m => FilePath -> MbtilesT m a -> m (Either MBTilesError a) Source #

Given a path to an MBTiles file, run the MbtilesT action. This will open a connection to the MBTiles file, run the action, and then close the connection. Some validation will be performed first. Of course, we will check if the MBTiles file actually exists. If it does, we need to validate its schema according to the MBTiles spec.

runMbtiles :: FilePath -> MbtilesIO a -> IO (Either MBTilesError a) Source #

Specialized version of runMbtilesT to run in the IO monad.

Pooling

type MbtilesPool = Pool MbtilesData Source #

A pool of connections to an MBTiles database.

getMbtilesPool :: MonadIO m => FilePath -> m (Either MBTilesError MbtilesPool) Source #

Given a path to an MBTiles file, create a connection pool to an MBTiles database. This will perform the same validation as runMbtilesT.

runMbtilesPoolT :: MonadBaseControl IO m => MbtilesPool -> MbtilesT m a -> m a Source #

Given access to an MbtilesPool, run an action against that pool.

Mbtiles read/write functionality

getTile :: (MonadIO m, FromTile a) => Z -> X -> Y -> MbtilesT m (Maybe a) Source #

Given a Z, X, and Y parameters, return the corresponding tile data, if it exists.

writeTile :: (MonadIO m, ToTile a) => Z -> X -> Y -> a -> MbtilesT m () Source #

Write new tile data to the tile at the specified Z, X, and Y parameters. This function assumes that the tile does not already exist.

writeTiles :: (MonadIO m, ToTile a) => [(Z, X, Y, a)] -> MbtilesT m () Source #

Batch write new tile data to the tile at the specified Z, X, and Y parameters. This function assumes that the tiles do not already exist.

updateTile :: (MonadIO m, ToTile a) => Z -> X -> Y -> a -> MbtilesT m () Source #

Update existing tile data for the tile at the specified Z, X, and Y parameters. This function assumes that the tile does already exist.

updateTiles :: (MonadIO m, ToTile a) => [(Z, X, Y, a)] -> MbtilesT m () Source #

Batch update tile data for the tiles at the specified Z, X, and Y parameters. This function assumes that the tiles do already exist.

Mbtiles metadata functionality

getMetadata :: MonadIO m => MbtilesT m MbtilesMeta Source #

Returns the MbtilesMeta that was found in the MBTiles file. This returns all of the currently available metadata for the MBTiles database.

getName :: MonadIO m => MbtilesT m Text Source #

Helper function for getting the specified name of the MBTiles from metadata.

getType :: MonadIO m => MbtilesT m Text Source #

Helper function for getting the type of the MBTiles from metadata.

getVersion :: MonadIO m => MbtilesT m Text Source #

Helper function for getting the version of the MBTiles from metadata.

getDescription :: MonadIO m => MbtilesT m Text Source #

Helper function for getting the description of the MBTiles from metadata.

getFormat :: MonadIO m => MbtilesT m Text Source #

Helper function for getting the format of the MBTiles from metadata.

Streaming tiles

data TileStream Source #

A TileStream data type contains information about how to stream tiles from the MBTiles database and is used in the same manner as an SQLite prepared statement.

startTileStream :: MonadIO m => MbtilesT m TileStream Source #

Create a TileStream data type that will be used to stream tiles from the MBTiles database. When streaming is complete, you must call endTileStream to clean up the TileStream resource. Tiles are streamed from the database in an ordered fashion, where they are sorted by zoom level, then tile column, then tile row, in ascending order.

endTileStream :: MonadIO m => TileStream -> MbtilesT m () Source #

Close a given TileStream when streaming is complete.

nextTile :: (MonadIO m, FromTile a) => TileStream -> MbtilesT m (Maybe (Tile a)) Source #

Receive the next Tile from the TileStream.