-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | A Haskell binding for H3
--
-- This package provides bindings to the H3 C API v4. H3 is a
-- geospatial indexing system that partitions the world into hexagonal
-- cells.
--
-- For users with experience with bindings for other languages, we
-- recommend reviewing the project README, as we have included notes for
-- using the methods provided in this package. In particular, as we bind
-- to the C methods with few adjustments to inputs and outputs beyond
-- data marshalling, there will be some differences for those familiar
-- with the python (and likely other) bindings, e.g. the methods provided
-- in this package expect the latitude and longitude to be in radians
-- rather than degrees.
@package h3-hs
@version 0.2.0.1
-- | This module collects the data types provided by the H3 API.
module H3.Data
-- | Latitude and longitude in radians
data LatLng
LatLng :: Double -> Double -> LatLng
-- | Latitude
[lat] :: LatLng -> Double
-- | Longitude
[lng] :: LatLng -> Double
-- | H3Index is a type synonym for Word64, which we use as the numeric
-- representation of the H3 index in Haskell
--
-- The C H3 error codes are modeled as a Haskell data type and instance
-- of Enum
type H3Index = Word64
data H3ErrorCodes
E_SUCCESS :: H3ErrorCodes
E_FAILED :: H3ErrorCodes
E_DOMAIN :: H3ErrorCodes
E_LATLNG_DOMAIN :: H3ErrorCodes
E_RES_DOMAIN :: H3ErrorCodes
E_CELL_INVALID :: H3ErrorCodes
E_DIR_EDGE_INVALID :: H3ErrorCodes
E_UNDIR_EDGE_INVALID :: H3ErrorCodes
E_VERTEX_INVALID :: H3ErrorCodes
E_PENTAGON :: H3ErrorCodes
E_DUPLICATE_INPUT :: H3ErrorCodes
E_NOT_NEIGHBORS :: H3ErrorCodes
E_RES_MISMATCH :: H3ErrorCodes
E_MEMORY_ALLOC :: H3ErrorCodes
E_MEMORY_BOUNDS :: H3ErrorCodes
E_OPTION_INVALID :: H3ErrorCodes
-- | A GeoLoop is defined as a list of LatLng in Haskell
type GeoLoop = [LatLng]
-- | A GeoPolygon has an exterior and interior holes, the exterior and each
-- interior hole being a GeoLoop
data GeoPolygon
GeoPolygon :: GeoLoop -> [GeoLoop] -> GeoPolygon
-- | Hexagon coordinates
data CoordIJ
CoordIJ :: Int -> Int -> CoordIJ
-- | These functions provide metadata about an H3 index, such as its
-- resolution or base cell, and provide utilities for converting into and
-- out of the 64-bit representation of an H3 index.
module H3.Inspection
-- | Returns the resolution of the index.
getResolution :: H3Index -> Int
-- | Returns the base cell number of the index.
getBaseCellNumber :: H3Index -> Int
-- | Converts the string representation to the H3Index (Word64)
-- representation.
stringToH3 :: String -> Either H3ErrorCodes H3Index
-- | Converts the H3Index representation to the string
-- representation.
h3ToString :: H3Index -> Either H3ErrorCodes String
-- | isValidCell returns non-zero if this is a valid H3 cell index
isValidCell :: H3Index -> Int
-- | Returns non-zero if this index has a resolution with Class III
-- orientation.
isResClassIII :: H3Index -> Int
-- | Returns non-zero if this index represents a pentagonal cell.
isPentagon :: H3Index -> Int
-- | Return all icosahedron faces intersected by a given H3 index. Faces
-- are represented as integers from 0-19, inclusive. The array is sparse,
-- and empty (no intersection) array values are represented by -1.
getIcosahedronFaces :: H3Index -> Either H3ErrorCodes [Int]
-- | These functions are used for finding the H3 cell index containing
-- coordinates, and for finding the center and boundary of H3 indexes.
module H3.Indexing
-- | Indexes the location at the specified resolution, returning the index
-- of the cell containing the location. This buckets the geographic point
-- into the H3 grid. Note that we are directly binding to the C method,
-- which expects Latitude and Longitude in radians. This differs from the
-- python bindings which expect the coordinates in degrees and perform
-- the necessary conversion for the user.
latLngToCell :: LatLng -> Int -> Either H3ErrorCodes H3Index
-- | Finds the center of the cell in grid space.
cellToLatLng :: H3Index -> Either H3ErrorCodes LatLng
-- | Finds the boundary of the cell, returning a list of coordinates.
cellToBoundary :: H3Index -> Either H3ErrorCodes [LatLng]
-- | These functions permit moving between resolutions in the H3 grid
-- system. The functions produce parent cells (coarser), or child cells
-- (finer).
module H3.Hierarchy
-- | Provides the parent index containing cell
cellToParent :: H3Index -> Int -> Either H3ErrorCodes H3Index
-- | Provides the center child index contained by cell at
-- resolution childRes.
cellToCenterChild :: H3Index -> Int -> Either H3ErrorCodes H3Index
-- | Returns the position of the child cell within an ordered list of all
-- children of the cell's parent at the specified resolution
-- parentRes. The order of the ordered list is the same as that
-- returned by cellToChildren. This is the complement of
-- childPosToCell.
cellToChildPos :: H3Index -> Int -> Either H3ErrorCodes Int64
-- | Returns the child cell at a given position within an ordered list of
-- all children of parent at the specified resolution
-- childRes. The order of the ordered list is the same as that
-- returned by cellToChildren. This is the complement of
-- cellToChildPos.
childPosToCell :: Int64 -> H3Index -> Int -> Either H3ErrorCodes H3Index
-- | Returns children with the indexes contained by cell at
-- resolution childRes.
cellToChildren :: H3Index -> Int -> Either H3ErrorCodes [H3Index]
-- | Compacts the set cellSet of indexes as best as possible.
-- Cells in cellSet must all share the same resolution.
compactCells :: [H3Index] -> Either H3ErrorCodes [H3Index]
-- | Uncompacts the set compactedSet of indexes to the resolution
-- res
uncompactCells :: [H3Index] -> Int -> Either H3ErrorCodes [H3Index]
-- | Directed edges allow encoding the directed edge from one cell to a
-- neighboring cell.
module H3.DirectedEdges
-- | Determines if the provided H3Index is a valid unidirectional
-- edge index.
isValidDirectedEdge :: H3Index -> Bool
-- | Returns a list of length 2 consisting of the origin and the
-- destination hexagon IDs for the given edge ID.
directedEdgeToCells :: H3Index -> Either H3ErrorCodes [H3Index]
-- | Provides all of the directed edges from the current H3Index.
-- The return will be of length 6, but the number of directed edges
-- placed in the array may be less than 6. If this is the case, one of
-- the members of the array will be 0.
originToDirectedEdges :: H3Index -> Either H3ErrorCodes [H3Index]
-- | Returns whether or not the provided H3 cell indexes are neighbors.
areNeighborCells :: H3Index -> H3Index -> Either H3ErrorCodes Bool
-- | Returns a unidirectional edge H3 index based on the provided
-- origin and destination.
cellsToDirectedEdge :: H3Index -> H3Index -> Either H3ErrorCodes H3Index
-- | Returns the origin hexagon from the unidirectional edge
-- H3Index.
getDirectedEdgeOrigin :: H3Index -> Either H3ErrorCodes H3Index
-- | Returns the destination hexagon from the unidirectional edge
-- H3Index.
getDirectedEdgeDestination :: H3Index -> Either H3ErrorCodes H3Index
-- | Provides the coordinates defining the unidirectional edge.
directedEdgeToBoundary :: H3Index -> Either H3ErrorCodes [LatLng]
-- | These methods in this module include
--
--
-- - general utilities to assist with activities such as unit
-- conversions, and
-- - methods for retrieving key information about the H3 indexing
-- system, such as pentagon cell ids, resolution 0 cells, etc.
--
module H3.Miscellaneous
-- | degsToRads converts from degrees to radians.
degsToRads :: Double -> Double
-- | radsToDegs converts from radians to degrees
radsToDegs :: Double -> Double
-- | All the resolution 0 H3 cell indexes. These are the coarsest cells
-- that can be represented in the H3 system and are the parents of all
-- other cell indexes in the H3 grid system. The returned indexes
-- correspond with the 122 base cells.
getRes0Cells :: Either H3ErrorCodes [H3Index]
-- | All the pentagon H3 indexes at the specified resolution.
getPentagons :: Int -> Either H3ErrorCodes [H3Index]
-- | Average hexagon area in square kilometers at the given resolution.
-- Excludes pentagons.
getHexagonAreaAvgKm2 :: Int -> Either H3ErrorCodes Double
-- | Average hexagon area in square meters at the given resolution.
-- Excludes pentagons.
getHexagonAreaAvgM2 :: Int -> Either H3ErrorCodes Double
-- | Exact area of specific cell in square radians.
cellAreaRads2 :: H3Index -> Either H3ErrorCodes Double
-- | Exact area of specific cell in square kilometers.
cellAreaKm2 :: H3Index -> Either H3ErrorCodes Double
-- | Exact area of specific cell in square meters.
cellAreaM2 :: H3Index -> Either H3ErrorCodes Double
-- | Average hexagon edge length in kilometers at the given resolution.
-- Excludes pentagons.
getHexagonEdgeLengthAvgKm :: Int -> Either H3ErrorCodes Double
-- | Average hexagon edge length in meters at the given resolution.
-- Excludes pentagons.
getHexagonEdgeLengthAvgM :: Int -> Either H3ErrorCodes Double
-- | Exact edge length of specific unidirectional edge in radians.
edgeLengthRads :: H3Index -> Either H3ErrorCodes Double
-- | Exact edge length of specific unidirectional edge in kilometers.
edgeLengthKm :: H3Index -> Either H3ErrorCodes Double
-- | Exact edge length of specific unidirectional edge in meters.
edgeLengthM :: H3Index -> Either H3ErrorCodes Double
-- | Number of unique H3 indexes at the given resolution.
getNumCells :: Int -> Either H3ErrorCodes Int64
-- | Gives the "great circle" or "haversine" distance between pairs of
-- LatLng points (lat/lng pairs) in kilometers.
greatCircleDistanceKm :: LatLng -> LatLng -> Double
-- | Gives the "great circle" or "haversine" distance between pairs of
-- LatLng points (lat/lng pairs) in meters.
greatCircleDistanceM :: LatLng -> LatLng -> Double
-- | Gives the "great circle" or "haversine" distance between pairs of
-- LatLng points (lat/lng pairs) in radians.
greatCircleDistanceRads :: LatLng -> LatLng -> Double
-- | These functions convert H3 indexes to and from polygonal areas.
module H3.Regions
-- | polygonToCells takes a given GeoJSON-like GeoPolygon
-- data structure and fills it with the hexagons that are contained in
-- the GeoPolygon. Containment is determined by the cells'
-- centroids. An argument for flags is provided, which is
-- reserved for future functionality, and should be taken to be 0 here.
polygonToCells :: GeoPolygon -> Int -> Word32 -> Either H3ErrorCodes [H3Index]
-- | Creates GeoPolygon describing the outline(s) of a set of
-- hexagons. Polygon outlines will have one outer loop and a list of
-- loops representing holes. It is expected that all hexagons in the set
-- have the same resolution and that the set contains no duplicates.
-- Behavior is undefined if duplicates or multiple resolutions are
-- present, and the algorithm may produce unexpected or invalid output.
cellsToLinkedMultiPolygon :: [H3Index] -> Either H3ErrorCodes [GeoPolygon]
-- | Grid traversal allows finding cells in the vicinity of an origin cell,
-- and determining how to traverse the grid from one cell to another.
module H3.Traversal
-- | gridDisk produces indices within k distance of the
-- origin index. Elements of the output array may be left as
-- zero, which can happen when crossing a pentagon.
gridDisk :: H3Index -> Int -> Either H3ErrorCodes [H3Index]
-- | gridDiskUnsafe produces indexes within k distance of the
-- origin index. The function returns an error code when one of
-- the returned by this function is a pentagon or is in the pentagon
-- distortion area. In this case, the output behavior of the out array is
-- undefined.
gridDiskUnsafe :: H3Index -> Int -> Either H3ErrorCodes [H3Index]
-- | gridDiskDistances produces indices within k distance of the
-- origin index. k-ring 0 is defined as the origin index, k-ring
-- 1 is defined as k-ring 0 and all neighboring indices, and so on.
gridDiskDistances :: H3Index -> Int -> Either H3ErrorCodes ([H3Index], [Int])
-- | gridDiskDistancesSafe produces indexes within k distance of
-- the origin index. While testing the Haskell bindings, we have
-- found issues with this function hanging. This does not appear to
-- happen with gridDiskDistances and
-- gridDiskDistancesUnsafe, though the official H3 documentation
-- should be consulted for further details about these functions. We
-- continue to make this function available for now, but it should be
-- noted that use of this function may cause issues.
gridDiskDistancesSafe :: H3Index -> Int -> Either H3ErrorCodes ([H3Index], [Int])
-- | gridDiskDistancesUnsafe produces indexes within k distance of
-- the origin index. Output behavior is undefined when one of
-- the indexes returned by this function is a pentagon or is in the
-- pentagon distortion area.
gridDiskDistancesUnsafe :: H3Index -> Int -> Either H3ErrorCodes ([H3Index], [Int])
-- | Produces the hollow hexagonal ring centered at origin with
-- sides of length k. In this Haskell method, zeros have been
-- removed from the resulting list of H3 indexes.
gridRingUnsafe :: H3Index -> Int -> Either H3ErrorCodes [H3Index]
-- | Given two H3 indexes, return the line of indexes between them
-- (inclusive). This function may fail to find the line between two
-- indexes, for example if they are very far apart. It may also fail when
-- finding distances for indexes on opposite sides of a pentagon.
--
-- Notes:
--
--
-- - The specific output of this function should not be considered
-- stable across library versions. The only guarantees the library
-- provides are that the line length will be consistent with the distance
-- method and that every index in the line will be a neighbor of the
-- preceding index.
-- - Lines are drawn in grid space, and may not correspond exactly to
-- either Cartesian lines or great arcs.
--
gridPathCells :: H3Index -> H3Index -> Either H3ErrorCodes [H3Index]
-- | Provides the distance in grid cells between the two indexes. Returns
-- an error if finding the distance failed. Finding the distance can fail
-- because the two indexes are not comparable (different resolutions),
-- too far apart, or are separated by pentagonal distortion. This is the
-- same set of limitations as the local IJ coordinate space functions.
gridDistance :: H3Index -> H3Index -> Either H3ErrorCodes Int64
-- | Produces local IJ coordinates for an H3 index anchored by an
-- origin. The C API has an additional argument mode which is
-- reserved for future expansion and must be set to 0. The method
-- provided here automatically passes the value. This function's output
-- is not guaranteed to be compatible across different versions of H3.
cellToLocalIj :: H3Index -> H3Index -> Either H3ErrorCodes CoordIJ
-- | Produces an H3 index from local IJ coordinates anchored by an
-- origin. The C API has an additional argument mode which is
-- reserved for future expansion and must be set to 0, and the method
-- defined here automatically passes the value. This function's output is
-- not guaranteed to be compatible across different versions of H3.
localIjToCell :: H3Index -> CoordIJ -> Either H3ErrorCodes H3Index
-- | Vertex mode allows encoding the topological vertexes of H3 cells.
module H3.Vertexes
-- | Returns the index for the specified cell vertex and vertex number.
-- Valid vertex numbers are between 0 and 5 (inclusive) for hexagonal
-- cells, and 0 and 4 (inclusive) for pentagonal cells.
cellToVertex :: H3Index -> Int -> Either H3ErrorCodes H3Index
-- | Returns the indexes for all vertexes of the given cell index. The
-- length of the returned list is 6. If the given cell index represents a
-- pentagon, one member of the list will be set to 0.
cellToVertexes :: H3Index -> Either H3ErrorCodes [H3Index]
-- | Returns the latitude and longitude coordinates of the given vertex.
vertexToLatLng :: H3Index -> Either H3ErrorCodes LatLng
-- | Returns True if the given index represents a valid H3 vertex.
isValidVertex :: H3Index -> Bool