mapalgebra
Efficient, polymorphic Map Algebra for Haskell.
This library is an implementation of Map Algebra as described in the
book GIS and Cartographic Modeling by Dana Tomlin. The fundamental
primitive is the Raster
, a rectangular grid of data that usually describes
some area on the earth.
mapalgebra
is built on top of massiv,
a powerful Parallel Array library by Alexey Kuleshevich.
Usage
Always compile with -threaded
, -O2
, and -with-rtsopts=-N
for best
performance.
The Raster
Type
This library provides Raster
s which are lazy, polymorphic, and typesafe. They
can hold any kind of data, and are aware of their projection and dimensions
at the type level. This means that imagery of different size or projection
are considered completely different types, which prevents an entire class
of bugs.
Raster
s have types signatures like this:
Raster S LatLng 256 256 Int
Raster D WebMercator 512 512 Word8
Raster DW p 1024 1024 (Maybe Double)
Reading Imagery
mapalgebra
can currently read any image file of any value type, so long as
it is grayscale (singleband) or RGBA. True multiband rasters (like from LandSat)
are not yet supported.
To read a Raster:
getRaster :: IO (Raster S p 512 512 Word8)
getRaster = do
erast <- fromGray "path/to/image.tif"
case erast of
Left err -> ...
Right r -> pure r
Colouring and Viewing Imagery
To quickly view a Raster you're working on, use the display
function:
display :: Raster D p r c a -> IO ()
This will automatically colour gray, evaluate, and display your Raster
using your OS's default image viewer.
To colour a Raster gray yourself, use grayscale
:
grayscale :: Functor (Raster u p r c) => Raster u p r c a -> Raster u p r c (Pixel Y a)
True colouring is done with the classify
function and colour ramps inspired by
Gretchen N. Peterson's book Cartographer's Toolkit.
classify :: (Ord a, Functor f) => b -> Map a b -> f a -> f b
invisible :: Pixel RGBA Word8
spectrum :: Ord k => [k] -> Map k (Pixel RGBA Word8)
We can generate the breaks via histogram
and breaks
(currently supports Word8
only):
colourIt :: Raster S p r c Word8 -> Raster S p r c (Pixel RGBA Word8)
colourIt r = strict S . classify invisible cm $ lazy r
where cm = spectrum . breaks $ histogram r
Before-and-after:

Local Operations
All Local Operations defined in GIS and Cartographic Modeling are available.
For the usual math ops, Raster D
has a Num
instance:
rast :: Raster D p 512 512 Int
squared :: Raster D p 512 512 Int
squared = rast * rast
Focal Operations
Except for Focal Ranking and Focal Insularity, all Focal Operations of immedatiate
neighbourhoods are provided:
rast :: Raster S p 512 512 Double
averagedPlusAbit :: Raster S p 512 512 Double
averagedPlusAbit = strict S . fmap (+1) $ fmean rast
Typesafe NoData Handling
If it's known that your images have large areas of NoData, consider that Maybe
has a Monoid
instance:
import Data.Monoid (Sum(..))
nodatafsum :: Raster S p r c Word8 -> Raster DW p r c 512 Word8
nodatafsum = fmap (maybe 0 getSum) . fmonoid . strict B . fmap check . lazy
where check 0 = Nothing
check n = Just $ Sum n
In theory, one could construct special newtype
wrappers with Monoid
instances
that handle any Focal scenario imaginable.
Future Work
- Projection handling at IO time
- Histogram generation for more data types
- Reprojections
- Extended neighbourhoods for Focal Ops
- Upsampling and Downsampling
- Improved NoData handling