{-# LINE 1 "src/H3/Internal/H3Api.chs" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module H3.Internal.H3Api
  ( H3ErrorCodes(..)
  , H3Error
  , H3Index
  , LatLng(LatLng, lat, lng)
  , c2hs_latLngToCell
  , c2hs_cellToLatLng
  , c2hs_cellToBoundary
  , c2hs_h3ToString
  , c2hs_stringToH3
  , GeoLoop
  , GeoPolygon(GeoPolygon)
  , CGeoPolygon
  , newCGeoPolygonPtr 
  , destroyCGeoPolygonPtr
  , hsCellsToLinkedMultiPolygon
  , c2hs_getHexagonAreaAvgKm2 
  , c2hs_getHexagonAreaAvgM2 
  , c2hs_cellAreaRads2
  , c2hs_cellAreaKm2
  , c2hs_cellAreaM2
  , c2hs_getHexagonEdgeLengthAvgKm
  , c2hs_getHexagonEdgeLengthAvgM
  , c2hs_edgeLengthRads
  , c2hs_edgeLengthKm
  , c2hs_edgeLengthM
  , c2hs_getNumCells
  , greatCircleDistanceKm
  , greatCircleDistanceM
  , greatCircleDistanceRads
  , c2hs_gridDistance
  , c2hs_cellToLocalIj
  , c2hs_localIjToCell
  , CoordIJ(CoordIJ)
  , c2hs_cellToParent
  , c2hs_cellToCenterChild
  , c2hs_cellToChildPos
  , c2hs_childPosToCell 
  , c2hs_areNeighborCells
  , c2hs_cellsToDirectedEdge
  , c2hs_getDirectedEdgeOrigin
  , c2hs_getDirectedEdgeDestination
  , c2hs_directedEdgeToBoundary
  , c2hs_cellToVertex
  , c2hs_vertexToLatLng
  ) where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.ForeignPtr as C2HSImp
import qualified Foreign.Marshal.Array as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
import qualified System.IO.Unsafe as C2HSImp
import Control.Monad (liftM2, liftM3)
import Data.Int(Int64)
import Data.Word (Word64, Word32)
import System.IO.Unsafe (unsafePerformIO)
import Foreign.C.Types (CULong, CLong, CInt(CInt), CDouble(CDouble))
import Foreign.Ptr (Ptr, castPtr, nullPtr)
import Foreign.Marshal.Array (withArrayLen, peekArray, newArray)
import Foreign.Marshal.Utils (with)
import Foreign.Marshal.Alloc (alloca, malloc, free)
import Foreign.C.String (CString, withCStringLen, peekCString, withCString)
import Foreign.Storable (Storable(peek, poke))
import Foreign.ForeignPtr (withForeignPtr, FinalizerPtr, addForeignPtrFinalizer, mallocForeignPtr)
data H3ErrorCodes = E_SUCCESS
                  | E_FAILED
                  | E_DOMAIN
                  | E_LATLNG_DOMAIN
                  | E_RES_DOMAIN
                  | E_CELL_INVALID
                  | E_DIR_EDGE_INVALID
                  | E_UNDIR_EDGE_INVALID
                  | E_VERTEX_INVALID
                  | E_PENTAGON
                  | E_DUPLICATE_INPUT
                  | E_NOT_NEIGHBORS
                  | E_RES_MISMATCH
                  | E_MEMORY_ALLOC
                  | E_MEMORY_BOUNDS
                  | E_OPTION_INVALID
  deriving (Show,Eq)
instance Enum H3ErrorCodes where
  succ E_SUCCESS = E_FAILED
  succ E_FAILED = E_DOMAIN
  succ E_DOMAIN = E_LATLNG_DOMAIN
  succ E_LATLNG_DOMAIN = E_RES_DOMAIN
  succ E_RES_DOMAIN = E_CELL_INVALID
  succ E_CELL_INVALID = E_DIR_EDGE_INVALID
  succ E_DIR_EDGE_INVALID = E_UNDIR_EDGE_INVALID
  succ E_UNDIR_EDGE_INVALID = E_VERTEX_INVALID
  succ E_VERTEX_INVALID = E_PENTAGON
  succ E_PENTAGON = E_DUPLICATE_INPUT
  succ E_DUPLICATE_INPUT = E_NOT_NEIGHBORS
  succ E_NOT_NEIGHBORS = E_RES_MISMATCH
  succ E_RES_MISMATCH = E_MEMORY_ALLOC
  succ E_MEMORY_ALLOC = E_MEMORY_BOUNDS
  succ E_MEMORY_BOUNDS = E_OPTION_INVALID
  succ E_OPTION_INVALID = error "H3ErrorCodes.succ: E_OPTION_INVALID has no successor"
  pred E_FAILED = E_SUCCESS
  pred E_DOMAIN = E_FAILED
  pred E_LATLNG_DOMAIN = E_DOMAIN
  pred E_RES_DOMAIN = E_LATLNG_DOMAIN
  pred E_CELL_INVALID = E_RES_DOMAIN
  pred E_DIR_EDGE_INVALID = E_CELL_INVALID
  pred E_UNDIR_EDGE_INVALID = E_DIR_EDGE_INVALID
  pred E_VERTEX_INVALID = E_UNDIR_EDGE_INVALID
  pred E_PENTAGON = E_VERTEX_INVALID
  pred E_DUPLICATE_INPUT = E_PENTAGON
  pred E_NOT_NEIGHBORS = E_DUPLICATE_INPUT
  pred E_RES_MISMATCH = E_NOT_NEIGHBORS
  pred E_MEMORY_ALLOC = E_RES_MISMATCH
  pred E_MEMORY_BOUNDS = E_MEMORY_ALLOC
  pred E_OPTION_INVALID = E_MEMORY_BOUNDS
  pred E_SUCCESS = error "H3ErrorCodes.pred: E_SUCCESS has no predecessor"
  enumFromTo :: H3ErrorCodes -> H3ErrorCodes -> [H3ErrorCodes]
enumFromTo H3ErrorCodes
from H3ErrorCodes
to = H3ErrorCodes -> [H3ErrorCodes]
forall {t}. Enum t => t -> [t]
go H3ErrorCodes
from
    where
      end :: Int
end = H3ErrorCodes -> Int
forall a. Enum a => a -> Int
fromEnum H3ErrorCodes
to
      go :: t -> [t]
go t
v = case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (t -> Int
forall a. Enum a => a -> Int
fromEnum t
v) Int
end of
                 Ordering
LT -> t
v t -> [t] -> [t]
forall a. a -> [a] -> [a]
: t -> [t]
go (t -> t
forall a. Enum a => a -> a
succ t
v)
                 Ordering
EQ -> [t
v]
                 Ordering
GT -> []
  enumFrom from = enumFromTo from E_OPTION_INVALID
  fromEnum E_SUCCESS = 0
  fromEnum E_FAILED = 1
  fromEnum E_DOMAIN = 2
  fromEnum E_LATLNG_DOMAIN = 3
  fromEnum E_RES_DOMAIN = 4
  fromEnum E_CELL_INVALID = 5
  fromEnum E_DIR_EDGE_INVALID = 6
  fromEnum E_UNDIR_EDGE_INVALID = 7
  fromEnum E_VERTEX_INVALID = 8
  fromEnum E_PENTAGON = 9
  fromEnum E_DUPLICATE_INPUT = 10
  fromEnum E_NOT_NEIGHBORS = 11
  fromEnum E_RES_MISMATCH = 12
  fromEnum E_MEMORY_ALLOC = 13
  fromEnum E_MEMORY_BOUNDS = 14
  fromEnum E_OPTION_INVALID = 15
  toEnum 0 = E_SUCCESS
  toEnum 1 = E_FAILED
  toEnum 2 = E_DOMAIN
  toEnum 3 = E_LATLNG_DOMAIN
  toEnum 4 = E_RES_DOMAIN
  toEnum 5 = E_CELL_INVALID
  toEnum 6 = E_DIR_EDGE_INVALID
  toEnum 7 = E_UNDIR_EDGE_INVALID
  toEnum 8 = E_VERTEX_INVALID
  toEnum 9 = E_PENTAGON
  toEnum 10 = E_DUPLICATE_INPUT
  toEnum 11 = E_NOT_NEIGHBORS
  toEnum 12 = E_RES_MISMATCH
  toEnum 13 = E_MEMORY_ALLOC
  toEnum 14 = E_MEMORY_BOUNDS
  toEnum 15 = E_OPTION_INVALID
  toEnum unmatched = error ("H3ErrorCodes.toEnum: Cannot match " ++ show unmatched)
{-# LINE 66 "src/H3/Internal/H3Api.chs" #-}
type H3Error = Word32
type H3Index = Word64
data LatLng = LatLng 
    { lat :: Double 
    , lng :: Double 
    }
  deriving (Eq, Show)
instance Storable LatLng where
    sizeOf _ = 16
{-# LINE 84 "src/H3/Internal/H3Api.chs" #-}
    alignment _ = 8
{-# LINE 85 "src/H3/Internal/H3Api.chs" #-}
    peek p = do
      CDouble _lat <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CDouble}) p
      CDouble _lng <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CDouble}) p
      return $ LatLng _lat _lng
    poke p (LatLng x y) = do
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CDouble)}) p (CDouble x)
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CDouble)}) p (CDouble y)
type LatLngPtr = C2HSImp.Ptr (LatLng)
{-# LINE 95 "src/H3/Internal/H3Api.chs" #-}
peekH3Index :: Ptr CULong -> IO Word64
peekH3Index ptr = fromIntegral <$> peek ptr
c2hs_latLngToCell :: (LatLng) -> (Int) -> ((H3Error), (H3Index))
c2hs_latLngToCell a1 a2 =
  C2HSImp.unsafePerformIO $
  with a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  c2hs_latLngToCell'_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  peekH3Index  a3'>>= \a3'' -> 
  return (res', a3'')
{-# LINE 104 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellToLatLng :: (H3Index) -> ((H3Error), (LatLng))
c2hs_cellToLatLng a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_cellToLatLng'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peek  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 109 "src/H3/Internal/H3Api.chs" #-}
maxCellBndryVerts :: Int
maxCellBndryVerts = 10
{-# LINE 112 "src/H3/Internal/H3Api.chs" #-}
data CellBoundary = CellBoundary
    { callboundary_numVerts :: CInt
    , callboundary_verts :: Ptr LatLng
    }
  deriving (Eq, Show)
instance Storable CellBoundary where
    sizeOf _ = 168
{-# LINE 122 "src/H3/Internal/H3Api.chs" #-}
    alignment _ = 8
{-# LINE 123 "src/H3/Internal/H3Api.chs" #-}
    peek p = CellBoundary <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
                          <*> (\ptr -> do {return $ ptr `C2HSImp.plusPtr` 8 :: IO (LatLngPtr)}) p
    poke p (CellBoundary _num _verts) = do
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CInt)}) p _num
        (\ptr val -> do {C2HSImp.copyArray (ptr `C2HSImp.plusPtr` 8) (val :: (LatLngPtr)) 10}) p _verts
type CellBoundaryPtr = C2HSImp.Ptr (CellBoundary)
{-# LINE 130 "src/H3/Internal/H3Api.chs" #-}
withPlaceholderCellBoundary :: (Ptr CellBoundary -> IO b) -> IO b
withPlaceholderCellBoundary f =
  let dummyBoundary = replicate maxCellBndryVerts (LatLng 0 0)
  in withArrayLen dummyBoundary $ \num llptr -> do
       with (CellBoundary (fromIntegral num) llptr) f
cellBoundaryToLatLngs :: CellBoundaryPtr -> IO [LatLng]
cellBoundaryToLatLngs cellptr = do
      CellBoundary resnum resllptr <- peek cellptr
      resll <- peekArray (fromIntegral resnum) resllptr
      return resll
c2hs_cellToBoundary :: (H3Index) -> ((H3Error), ([LatLng]))
c2hs_cellToBoundary a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  withPlaceholderCellBoundary $ \a2' -> 
  c2hs_cellToBoundary'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  cellBoundaryToLatLngs  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 147 "src/H3/Internal/H3Api.chs" #-}
allocaCStringLen :: ((CString, CULong)-> IO a) -> IO a
allocaCStringLen fn = withCStringLen dummyString fnint
    where dummyString = replicate 17 '0'
          fnint (cstr, i) = fn (cstr, fromIntegral i)
peekCStringIgnoreLen :: CString -> CULong -> IO String
peekCStringIgnoreLen cstr _ = peekCString cstr
c2hs_h3ToString :: (H3Index) -> ((H3Error), (String))
c2hs_h3ToString a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  allocaCStringLen $ \(a2'1, a2'2) -> 
  c2hs_h3ToString'_ a1' a2'1  a2'2 >>= \res ->
  let {res' = fromIntegral res} in
  peekCStringIgnoreLen  a2'1  a2'2>>= \a2'' -> 
  return (res', a2'')
{-# LINE 162 "src/H3/Internal/H3Api.chs" #-}
c2hs_stringToH3 :: (String) -> ((H3Error), (H3Index))
c2hs_stringToH3 a1 =
  C2HSImp.unsafePerformIO $
  withCString a1 $ \a1' -> 
  alloca $ \a2' -> 
  c2hs_stringToH3'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekH3Index  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 167 "src/H3/Internal/H3Api.chs" #-}
data CGeoLoop = CGeoLoop
    { cgeoloop_numVerts :: CInt
    , cgeoloop_verts :: Ptr LatLng
    }
  deriving (Show)
instance Storable CGeoLoop where
    sizeOf :: CGeoLoop -> Int
sizeOf CGeoLoop
_ = Int
16
{-# LINE 178 "src/H3/Internal/H3Api.chs" #-}
    alignment _ = 8
{-# LINE 179 "src/H3/Internal/H3Api.chs" #-}
    peek p = liftM2 CGeoLoop ((\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p)
                             ((\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (LatLngPtr)}) p)
    poke :: Ptr CGeoLoop -> CGeoLoop -> IO ()
poke Ptr CGeoLoop
p (CGeoLoop CInt
numVerts Ptr LatLng
verts) = do
        (\Ptr CGeoLoop
ptr CInt
val -> do {Ptr CGeoLoop -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CGeoLoop
ptr Int
0 (CInt
val :: C2HSImp.CInt)}) Ptr CGeoLoop
p CInt
numVerts
        (\Ptr CGeoLoop
ptr Ptr LatLng
val -> do {Ptr CGeoLoop -> Int -> Ptr LatLng -> IO ()
forall b. Ptr b -> Int -> Ptr LatLng -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CGeoLoop
ptr Int
8 (Ptr LatLng
val :: (LatLngPtr))}) Ptr CGeoLoop
p Ptr LatLng
verts
newCGeoLoop :: GeoLoop -> IO CGeoLoop
newCGeoLoop :: [LatLng] -> IO CGeoLoop
newCGeoLoop [LatLng]
gl =
  if [LatLng] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [LatLng]
gl Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  then do
    Ptr LatLng
ptr <- [LatLng] -> IO (Ptr LatLng)
forall a. Storable a => [a] -> IO (Ptr a)
newArray [LatLng]
gl
    CGeoLoop -> IO CGeoLoop
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CGeoLoop -> IO CGeoLoop) -> CGeoLoop -> IO CGeoLoop
forall a b. (a -> b) -> a -> b
$ CInt -> Ptr LatLng -> CGeoLoop
CGeoLoop CInt
numVerts Ptr LatLng
ptr
  else CGeoLoop -> IO CGeoLoop
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CGeoLoop -> IO CGeoLoop) -> CGeoLoop -> IO CGeoLoop
forall a b. (a -> b) -> a -> b
$ CInt -> Ptr LatLng -> CGeoLoop
CGeoLoop CInt
0 Ptr LatLng
forall a. Ptr a
nullPtr
  where numVerts :: CInt
numVerts = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ [LatLng] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [LatLng]
gl
destroyCGeoLoop :: CGeoLoop -> IO ()
destroyCGeoLoop :: CGeoLoop -> IO ()
destroyCGeoLoop (CGeoLoop CInt
numVerts Ptr LatLng
vertsPtr) = 
  if CInt
numVerts CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
> CInt
0
  then do
    Ptr LatLng -> IO ()
forall a. Ptr a -> IO ()
free Ptr LatLng
vertsPtr
  else () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
data CGeoPolygon = CGeoPolygon 
    { CGeoPolygon -> CGeoLoop
cgeopoly_exterior :: CGeoLoop
    , CGeoPolygon -> CInt
cgeopoly_numHoles :: CInt
    , CGeoPolygon -> Ptr CGeoLoop
cgeopoly_holes :: Ptr CGeoLoop
    } 
  deriving (Int -> CGeoPolygon -> ShowS
[CGeoPolygon] -> ShowS
CGeoPolygon -> String
(Int -> CGeoPolygon -> ShowS)
-> (CGeoPolygon -> String)
-> ([CGeoPolygon] -> ShowS)
-> Show CGeoPolygon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CGeoPolygon -> ShowS
showsPrec :: Int -> CGeoPolygon -> ShowS
$cshow :: CGeoPolygon -> String
show :: CGeoPolygon -> String
$cshowList :: [CGeoPolygon] -> ShowS
showList :: [CGeoPolygon] -> ShowS
Show)
instance Storable CGeoPolygon where
    sizeOf :: CGeoPolygon -> Int
sizeOf CGeoPolygon
_ = Int
32
{-# LINE 210 "src/H3/Internal/H3Api.chs" #-}
    alignment _ = 8
{-# LINE 211 "src/H3/Internal/H3Api.chs" #-}
    peek p = liftM3 CGeoPolygon (peekExterior p)
                                ((\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO C2HSImp.CInt}) p)
                                (castPtr <$> (\ptr -> do {C2HSImp.peekByteOff ptr 24 :: IO (C2HSImp.Ptr ())}) p)
        where peekExterior p0 = liftM2 CGeoLoop ((\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p0) ((\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (LatLngPtr)}) p0)
    poke :: Ptr CGeoPolygon -> CGeoPolygon -> IO ()
poke Ptr CGeoPolygon
p (CGeoPolygon (CGeoLoop CInt
numVerts Ptr LatLng
verts) CInt
numHoles Ptr CGeoLoop
holes) = do
        (\Ptr CGeoPolygon
ptr CInt
val -> do {Ptr CGeoPolygon -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CGeoPolygon
ptr Int
0 (CInt
val :: C2HSImp.CInt)}) Ptr CGeoPolygon
p CInt
numVerts
        (\Ptr CGeoPolygon
ptr Ptr LatLng
val -> do {Ptr CGeoPolygon -> Int -> Ptr LatLng -> IO ()
forall b. Ptr b -> Int -> Ptr LatLng -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CGeoPolygon
ptr Int
8 (Ptr LatLng
val :: (LatLngPtr))}) Ptr CGeoPolygon
p Ptr LatLng
verts
        (\Ptr CGeoPolygon
ptr CInt
val -> do {Ptr CGeoPolygon -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CGeoPolygon
ptr Int
16 (CInt
val :: C2HSImp.CInt)}) Ptr CGeoPolygon
p CInt
numHoles
        (\Ptr CGeoPolygon
ptr Ptr ()
val -> do {Ptr CGeoPolygon -> Int -> Ptr () -> IO ()
forall b. Ptr b -> Int -> Ptr () -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CGeoPolygon
ptr Int
24 (Ptr ()
val :: (C2HSImp.Ptr ()))}) Ptr CGeoPolygon
p (Ptr CGeoLoop -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CGeoLoop
holes)
type GeoLoop = [LatLng]
data GeoPolygon = GeoPolygon
   { GeoPolygon -> [LatLng]
geopoly_exterior :: GeoLoop 
   , GeoPolygon -> [[LatLng]]
geopoly_holes :: [GeoLoop]  
   }
  deriving (GeoPolygon -> GeoPolygon -> Bool
(GeoPolygon -> GeoPolygon -> Bool)
-> (GeoPolygon -> GeoPolygon -> Bool) -> Eq GeoPolygon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GeoPolygon -> GeoPolygon -> Bool
== :: GeoPolygon -> GeoPolygon -> Bool
$c/= :: GeoPolygon -> GeoPolygon -> Bool
/= :: GeoPolygon -> GeoPolygon -> Bool
Eq, Int -> GeoPolygon -> ShowS
[GeoPolygon] -> ShowS
GeoPolygon -> String
(Int -> GeoPolygon -> ShowS)
-> (GeoPolygon -> String)
-> ([GeoPolygon] -> ShowS)
-> Show GeoPolygon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GeoPolygon -> ShowS
showsPrec :: Int -> GeoPolygon -> ShowS
$cshow :: GeoPolygon -> String
show :: GeoPolygon -> String
$cshowList :: [GeoPolygon] -> ShowS
showList :: [GeoPolygon] -> ShowS
Show)
newCGeoPolygon :: GeoPolygon -> IO CGeoPolygon
newCGeoPolygon :: GeoPolygon -> IO CGeoPolygon
newCGeoPolygon (GeoPolygon [LatLng]
exterior [[LatLng]]
holes) = do
  CGeoLoop
cext <- [LatLng] -> IO CGeoLoop
newCGeoLoop [LatLng]
exterior
  Ptr CGeoLoop
cholesPtr <- if CInt
numHoles CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
> CInt
0
               then do
                 [CGeoLoop]
choles <- ([LatLng] -> IO CGeoLoop) -> [[LatLng]] -> IO [CGeoLoop]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM [LatLng] -> IO CGeoLoop
newCGeoLoop [[LatLng]]
holes
                 [CGeoLoop] -> IO (Ptr CGeoLoop)
forall a. Storable a => [a] -> IO (Ptr a)
newArray [CGeoLoop]
choles
               else Ptr CGeoLoop -> IO (Ptr CGeoLoop)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CGeoLoop
forall a. Ptr a
nullPtr
  CGeoPolygon -> IO CGeoPolygon
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CGeoPolygon -> IO CGeoPolygon) -> CGeoPolygon -> IO CGeoPolygon
forall a b. (a -> b) -> a -> b
$ CGeoLoop -> CInt -> Ptr CGeoLoop -> CGeoPolygon
CGeoPolygon CGeoLoop
cext CInt
numHoles Ptr CGeoLoop
cholesPtr
  where numHoles :: CInt
numHoles = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Int -> CInt
forall a b. (a -> b) -> a -> b
$ [[LatLng]] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[LatLng]]
holes
newCGeoPolygonPtr :: GeoPolygon -> IO (Ptr CGeoPolygon)
newCGeoPolygonPtr :: GeoPolygon -> IO (Ptr CGeoPolygon)
newCGeoPolygonPtr GeoPolygon
gp = do
  Ptr CGeoPolygon
ptr <- IO (Ptr CGeoPolygon)
forall a. Storable a => IO (Ptr a)
malloc 
  CGeoPolygon
cgp <- GeoPolygon -> IO CGeoPolygon
newCGeoPolygon GeoPolygon
gp
  Ptr CGeoPolygon -> CGeoPolygon -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CGeoPolygon
ptr CGeoPolygon
cgp
  Ptr CGeoPolygon -> IO (Ptr CGeoPolygon)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CGeoPolygon
ptr
destroyCGeoPolygon :: CGeoPolygon -> IO ()
destroyCGeoPolygon :: CGeoPolygon -> IO ()
destroyCGeoPolygon (CGeoPolygon CGeoLoop
ext CInt
numHoles Ptr CGeoLoop
holesPtr) = do
  if CInt
numHoles CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
> CInt
0
  then do
    Int -> Ptr CGeoLoop -> IO [CGeoLoop]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
numHoles) Ptr CGeoLoop
holesPtr IO [CGeoLoop] -> ([CGeoLoop] -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (CGeoLoop -> IO ()) -> [CGeoLoop] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ CGeoLoop -> IO ()
destroyCGeoLoop 
    Ptr CGeoLoop -> IO ()
forall a. Ptr a -> IO ()
free Ptr CGeoLoop
holesPtr
  else () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
  CGeoLoop -> IO ()
destroyCGeoLoop CGeoLoop
ext
destroyCGeoPolygonPtr :: Ptr CGeoPolygon -> IO ()
destroyCGeoPolygonPtr :: Ptr CGeoPolygon -> IO ()
destroyCGeoPolygonPtr Ptr CGeoPolygon
ptr = do
  Ptr CGeoPolygon -> IO CGeoPolygon
forall a. Storable a => Ptr a -> IO a
peek Ptr CGeoPolygon
ptr IO CGeoPolygon -> (CGeoPolygon -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CGeoPolygon -> IO ()
destroyCGeoPolygon
  Ptr CGeoPolygon -> IO ()
forall a. Ptr a -> IO ()
free Ptr CGeoPolygon
ptr
data CLinkedLatLng = CLinkedLatLng
    { CLinkedLatLng -> LatLng
clinkedlatlng_vertex :: LatLng
    , CLinkedLatLng -> Ptr CLinkedLatLng
clinkedlatlng_next :: Ptr CLinkedLatLng
    }
  deriving (Int -> CLinkedLatLng -> ShowS
[CLinkedLatLng] -> ShowS
CLinkedLatLng -> String
(Int -> CLinkedLatLng -> ShowS)
-> (CLinkedLatLng -> String)
-> ([CLinkedLatLng] -> ShowS)
-> Show CLinkedLatLng
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CLinkedLatLng -> ShowS
showsPrec :: Int -> CLinkedLatLng -> ShowS
$cshow :: CLinkedLatLng -> String
show :: CLinkedLatLng -> String
$cshowList :: [CLinkedLatLng] -> ShowS
showList :: [CLinkedLatLng] -> ShowS
Show)
extractLatLng :: Ptr CLinkedLatLng -> IO [LatLng]
 Ptr CLinkedLatLng
ptr | Ptr CLinkedLatLng
ptr Ptr CLinkedLatLng -> Ptr CLinkedLatLng -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CLinkedLatLng
forall a. Ptr a
nullPtr = Ptr CLinkedLatLng -> IO [LatLng]
processPtr Ptr CLinkedLatLng
ptr
                  | Bool
otherwise      = [LatLng] -> IO [LatLng]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
    where processPtr :: Ptr CLinkedLatLng -> IO [LatLng]
processPtr Ptr CLinkedLatLng
ptr0 = do 
              CLinkedLatLng LatLng
vertex Ptr CLinkedLatLng
nextptr <- Ptr CLinkedLatLng -> IO CLinkedLatLng
forall a. Storable a => Ptr a -> IO a
peek Ptr CLinkedLatLng
ptr0
              [LatLng]
followingValues <- Ptr CLinkedLatLng -> IO [LatLng]
extractLatLng Ptr CLinkedLatLng
nextptr
              [LatLng] -> IO [LatLng]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([LatLng] -> IO [LatLng]) -> [LatLng] -> IO [LatLng]
forall a b. (a -> b) -> a -> b
$ LatLng
vertex LatLng -> [LatLng] -> [LatLng]
forall a. a -> [a] -> [a]
: [LatLng]
followingValues
instance Storable CLinkedLatLng where
    sizeOf :: CLinkedLatLng -> Int
sizeOf CLinkedLatLng
_ = Int
24
{-# LINE 279 "src/H3/Internal/H3Api.chs" #-}
    alignment _ = 8
{-# LINE 280 "src/H3/Internal/H3Api.chs" #-}
    peek p = do
        CDouble llat <- (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CDouble}) p
        CDouble llng <- (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CDouble}) p
        llptr <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr ())}) p
        return $ CLinkedLatLng (LatLng llat llng) (castPtr llptr)
    poke :: Ptr CLinkedLatLng -> CLinkedLatLng -> IO ()
poke Ptr CLinkedLatLng
p (CLinkedLatLng (LatLng Double
latval Double
lngval) Ptr CLinkedLatLng
next) = do
        (\Ptr CLinkedLatLng
ptr CDouble
val -> do {Ptr CLinkedLatLng -> Int -> CDouble -> IO ()
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CLinkedLatLng
ptr Int
0 (CDouble
val :: C2HSImp.CDouble)}) Ptr CLinkedLatLng
p (Double -> CDouble
CDouble Double
latval)
        (\Ptr CLinkedLatLng
ptr CDouble
val -> do {Ptr CLinkedLatLng -> Int -> CDouble -> IO ()
forall b. Ptr b -> Int -> CDouble -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CLinkedLatLng
ptr Int
8 (CDouble
val :: C2HSImp.CDouble)}) Ptr CLinkedLatLng
p (Double -> CDouble
CDouble Double
lngval)
        (\Ptr CLinkedLatLng
ptr Ptr ()
val -> do {Ptr CLinkedLatLng -> Int -> Ptr () -> IO ()
forall b. Ptr b -> Int -> Ptr () -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CLinkedLatLng
ptr Int
16 (Ptr ()
val :: (C2HSImp.Ptr ()))}) Ptr CLinkedLatLng
p (Ptr CLinkedLatLng -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CLinkedLatLng
next)
data CLinkedGeoLoop = CLinkedGeoLoop 
    { CLinkedGeoLoop -> Ptr CLinkedLatLng
clinkedgeoloop_first :: Ptr CLinkedLatLng
    , CLinkedGeoLoop -> Ptr CLinkedLatLng
clinkedgeoloop_last :: Ptr CLinkedLatLng
    , CLinkedGeoLoop -> Ptr CLinkedGeoLoop
clinkedgeoloop_next :: Ptr CLinkedGeoLoop
    }
  deriving (Int -> CLinkedGeoLoop -> ShowS
[CLinkedGeoLoop] -> ShowS
CLinkedGeoLoop -> String
(Int -> CLinkedGeoLoop -> ShowS)
-> (CLinkedGeoLoop -> String)
-> ([CLinkedGeoLoop] -> ShowS)
-> Show CLinkedGeoLoop
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CLinkedGeoLoop -> ShowS
showsPrec :: Int -> CLinkedGeoLoop -> ShowS
$cshow :: CLinkedGeoLoop -> String
show :: CLinkedGeoLoop -> String
$cshowList :: [CLinkedGeoLoop] -> ShowS
showList :: [CLinkedGeoLoop] -> ShowS
Show)
extractGeoLoop :: Ptr CLinkedGeoLoop -> IO [GeoLoop]
 Ptr CLinkedGeoLoop
ptr | Ptr CLinkedGeoLoop
ptr Ptr CLinkedGeoLoop -> Ptr CLinkedGeoLoop -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CLinkedGeoLoop
forall a. Ptr a
nullPtr = Ptr CLinkedGeoLoop -> IO [[LatLng]]
processPtr Ptr CLinkedGeoLoop
ptr
                   | Bool
otherwise      = [[LatLng]] -> IO [[LatLng]]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
    where processPtr :: Ptr CLinkedGeoLoop -> IO [[LatLng]]
processPtr Ptr CLinkedGeoLoop
ptr0 = do 
              CLinkedGeoLoop Ptr CLinkedLatLng
llfirst Ptr CLinkedLatLng
_ Ptr CLinkedGeoLoop
glnext <- Ptr CLinkedGeoLoop -> IO CLinkedGeoLoop
forall a. Storable a => Ptr a -> IO a
peek Ptr CLinkedGeoLoop
ptr0
              [LatLng]
currentValue <- Ptr CLinkedLatLng -> IO [LatLng]
extractLatLng Ptr CLinkedLatLng
llfirst
              [[LatLng]]
followingValues <- Ptr CLinkedGeoLoop -> IO [[LatLng]]
extractGeoLoop Ptr CLinkedGeoLoop
glnext
              [[LatLng]] -> IO [[LatLng]]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([[LatLng]] -> IO [[LatLng]]) -> [[LatLng]] -> IO [[LatLng]]
forall a b. (a -> b) -> a -> b
$ [LatLng]
currentValue [LatLng] -> [[LatLng]] -> [[LatLng]]
forall a. a -> [a] -> [a]
: [[LatLng]]
followingValues
instance Storable CLinkedGeoLoop where
    sizeOf :: CLinkedGeoLoop -> Int
sizeOf CLinkedGeoLoop
_ = Int
24
{-# LINE 308 "src/H3/Internal/H3Api.chs" #-}
    alignment _ = 8
{-# LINE 309 "src/H3/Internal/H3Api.chs" #-}
    peek p = liftM3 CLinkedGeoLoop (castPtr <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr ())}) p) 
                                   (castPtr <$> (\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr ())}) p) 
                                   (castPtr <$> (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr ())}) p)
    poke :: Ptr CLinkedGeoLoop -> CLinkedGeoLoop -> IO ()
poke Ptr CLinkedGeoLoop
p (CLinkedGeoLoop Ptr CLinkedLatLng
cllfirst Ptr CLinkedLatLng
clllast Ptr CLinkedGeoLoop
cllnext) = do
        (\Ptr CLinkedGeoLoop
ptr Ptr ()
val -> do {Ptr CLinkedGeoLoop -> Int -> Ptr () -> IO ()
forall b. Ptr b -> Int -> Ptr () -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CLinkedGeoLoop
ptr Int
0 (Ptr ()
val :: (C2HSImp.Ptr ()))}) Ptr CLinkedGeoLoop
p (Ptr CLinkedLatLng -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CLinkedLatLng
cllfirst)
        (\Ptr CLinkedGeoLoop
ptr Ptr ()
val -> do {Ptr CLinkedGeoLoop -> Int -> Ptr () -> IO ()
forall b. Ptr b -> Int -> Ptr () -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CLinkedGeoLoop
ptr Int
8 (Ptr ()
val :: (C2HSImp.Ptr ()))}) Ptr CLinkedGeoLoop
p (Ptr CLinkedLatLng -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CLinkedLatLng
clllast)
        (\Ptr CLinkedGeoLoop
ptr Ptr ()
val -> do {Ptr CLinkedGeoLoop -> Int -> Ptr () -> IO ()
forall b. Ptr b -> Int -> Ptr () -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CLinkedGeoLoop
ptr Int
16 (Ptr ()
val :: (C2HSImp.Ptr ()))}) Ptr CLinkedGeoLoop
p (Ptr CLinkedGeoLoop -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CLinkedGeoLoop
cllnext)
data CLinkedGeoPolygon = CLinkedGeoPolygon 
    { CLinkedGeoPolygon -> Ptr CLinkedGeoLoop
clinkedgeopoly_first :: Ptr CLinkedGeoLoop
    , CLinkedGeoPolygon -> Ptr CLinkedGeoLoop
clinkedgeopoly_last :: Ptr CLinkedGeoLoop
    , CLinkedGeoPolygon -> Ptr CLinkedGeoPolygon
clinkedgeopoly_next :: Ptr CLinkedGeoPolygon
    }
  deriving (Int -> CLinkedGeoPolygon -> ShowS
[CLinkedGeoPolygon] -> ShowS
CLinkedGeoPolygon -> String
(Int -> CLinkedGeoPolygon -> ShowS)
-> (CLinkedGeoPolygon -> String)
-> ([CLinkedGeoPolygon] -> ShowS)
-> Show CLinkedGeoPolygon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CLinkedGeoPolygon -> ShowS
showsPrec :: Int -> CLinkedGeoPolygon -> ShowS
$cshow :: CLinkedGeoPolygon -> String
show :: CLinkedGeoPolygon -> String
$cshowList :: [CLinkedGeoPolygon] -> ShowS
showList :: [CLinkedGeoPolygon] -> ShowS
Show)
extractGeoPolygons :: Ptr CLinkedGeoPolygon -> IO [GeoPolygon]
 Ptr CLinkedGeoPolygon
ptr | Ptr CLinkedGeoPolygon
ptr Ptr CLinkedGeoPolygon -> Ptr CLinkedGeoPolygon -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CLinkedGeoPolygon
forall a. Ptr a
nullPtr = Ptr CLinkedGeoPolygon -> IO [GeoPolygon]
processPtr Ptr CLinkedGeoPolygon
ptr
                       | Bool
otherwise      = [GeoPolygon] -> IO [GeoPolygon]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []
    where processPtr :: Ptr CLinkedGeoPolygon -> IO [GeoPolygon]
processPtr Ptr CLinkedGeoPolygon
ptr0 = do 
              CLinkedGeoPolygon Ptr CLinkedGeoLoop
glfirst Ptr CLinkedGeoLoop
_ Ptr CLinkedGeoPolygon
gpnext <- Ptr CLinkedGeoPolygon -> IO CLinkedGeoPolygon
forall a. Storable a => Ptr a -> IO a
peek Ptr CLinkedGeoPolygon
ptr0
              [[LatLng]]
currentGeoLoops <- Ptr CLinkedGeoLoop -> IO [[LatLng]]
extractGeoLoop Ptr CLinkedGeoLoop
glfirst
              let currentValue :: GeoPolygon
currentValue = case [[LatLng]]
currentGeoLoops of 
                    [LatLng]
exterior : [[LatLng]]
holes -> [LatLng] -> [[LatLng]] -> GeoPolygon
GeoPolygon [LatLng]
exterior [[LatLng]]
holes
                    [[LatLng]]
_                -> [LatLng] -> [[LatLng]] -> GeoPolygon
GeoPolygon [] []
              [GeoPolygon]
followingValues <- Ptr CLinkedGeoPolygon -> IO [GeoPolygon]
extractGeoPolygons Ptr CLinkedGeoPolygon
gpnext
              [GeoPolygon] -> IO [GeoPolygon]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([GeoPolygon] -> IO [GeoPolygon])
-> [GeoPolygon] -> IO [GeoPolygon]
forall a b. (a -> b) -> a -> b
$ GeoPolygon
currentValue GeoPolygon -> [GeoPolygon] -> [GeoPolygon]
forall a. a -> [a] -> [a]
: [GeoPolygon]
followingValues
instance Storable CLinkedGeoPolygon where
    sizeOf :: CLinkedGeoPolygon -> Int
sizeOf CLinkedGeoPolygon
_ = Int
24
{-# LINE 338 "src/H3/Internal/H3Api.chs" #-}
    alignment _ = 8
{-# LINE 339 "src/H3/Internal/H3Api.chs" #-}
    peek p = liftM3 CLinkedGeoPolygon (castPtr <$> ((\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr ())}) p)) 
                                      (castPtr <$> ((\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO (C2HSImp.Ptr ())}) p))
                                      (castPtr <$> ((\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr ())}) p))
    poke :: Ptr CLinkedGeoPolygon -> CLinkedGeoPolygon -> IO ()
poke Ptr CLinkedGeoPolygon
p (CLinkedGeoPolygon Ptr CLinkedGeoLoop
clgfirst Ptr CLinkedGeoLoop
clglast Ptr CLinkedGeoPolygon
clgnext) = do
        (\Ptr CLinkedGeoPolygon
ptr Ptr ()
val -> do {Ptr CLinkedGeoPolygon -> Int -> Ptr () -> IO ()
forall b. Ptr b -> Int -> Ptr () -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CLinkedGeoPolygon
ptr Int
0 (Ptr ()
val :: (C2HSImp.Ptr ()))}) Ptr CLinkedGeoPolygon
p (Ptr CLinkedGeoLoop -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CLinkedGeoLoop
clgfirst)
        (\Ptr CLinkedGeoPolygon
ptr Ptr ()
val -> do {Ptr CLinkedGeoPolygon -> Int -> Ptr () -> IO ()
forall b. Ptr b -> Int -> Ptr () -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CLinkedGeoPolygon
ptr Int
8 (Ptr ()
val :: (C2HSImp.Ptr ()))}) Ptr CLinkedGeoPolygon
p (Ptr CLinkedGeoLoop -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CLinkedGeoLoop
clglast)
        (\Ptr CLinkedGeoPolygon
ptr Ptr ()
val -> do {Ptr CLinkedGeoPolygon -> Int -> Ptr () -> IO ()
forall b. Ptr b -> Int -> Ptr () -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr CLinkedGeoPolygon
ptr Int
16 (Ptr ()
val :: (C2HSImp.Ptr ()))}) Ptr CLinkedGeoPolygon
p (Ptr CLinkedGeoPolygon -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr Ptr CLinkedGeoPolygon
clgnext)
withArrayInput :: (Storable a) => [a] -> ((Ptr a, CInt) -> IO b) -> IO b
withArrayInput :: forall a b. Storable a => [a] -> ((Ptr a, CInt) -> IO b) -> IO b
withArrayInput [a]
as (Ptr a, CInt) -> IO b
fn =
    [a] -> (Int -> Ptr a -> IO b) -> IO b
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [a]
as ((Ptr a -> Int -> IO b) -> Int -> Ptr a -> IO b
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Ptr a -> Int -> IO b) -> Int -> Ptr a -> IO b)
-> (Ptr a -> Int -> IO b) -> Int -> Ptr a -> IO b
forall a b. (a -> b) -> a -> b
$ ((Ptr a, Int) -> IO b) -> Ptr a -> Int -> IO b
forall a b c. ((a, b) -> c) -> a -> b -> c
curry (Ptr a, Int) -> IO b
fnadj)
    where convertInt :: (a, a) -> (a, b)
convertInt (a
ptr, a
i) = (a
ptr, a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i)
          fnadj :: (Ptr a, Int) -> IO b
fnadj = (Ptr a, CInt) -> IO b
fn ((Ptr a, CInt) -> IO b)
-> ((Ptr a, Int) -> (Ptr a, CInt)) -> (Ptr a, Int) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Ptr a, Int) -> (Ptr a, CInt)
forall {a} {b} {a}. (Integral a, Num b) => (a, a) -> (a, b)
convertInt
withH3IndexArray :: [H3Index] -> ((Ptr CULong, CInt) -> IO b) -> IO b
withH3IndexArray :: forall b. [Word64] -> ((Ptr CULong, CInt) -> IO b) -> IO b
withH3IndexArray = [CULong] -> ((Ptr CULong, CInt) -> IO b) -> IO b
forall a b. Storable a => [a] -> ((Ptr a, CInt) -> IO b) -> IO b
withArrayInput ([CULong] -> ((Ptr CULong, CInt) -> IO b) -> IO b)
-> ([Word64] -> [CULong])
-> [Word64]
-> ((Ptr CULong, CInt) -> IO b)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Word64 -> CULong) -> [Word64] -> [CULong]
forall a b. (a -> b) -> [a] -> [b]
map Word64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral)
foreign import ccall "h3/h3api.h &destroyLinkedMultiPolygon"
  destroyLinkedMultiPolygon :: FinalizerPtr CLinkedGeoPolygon
type LinkedGeoPolygonFPtr = C2HSImp.ForeignPtr (CLinkedGeoPolygon)
{-# LINE 360 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellsToLinkedMultiPolygon :: ([H3Index]) -> (LinkedGeoPolygonFPtr) -> (H3Error)
c2hs_cellsToLinkedMultiPolygon :: [Word64] -> LinkedGeoPolygonFPtr -> H3Error
c2hs_cellsToLinkedMultiPolygon [Word64]
a1 LinkedGeoPolygonFPtr
a2 =
  IO H3Error -> H3Error
forall a. IO a -> a
C2HSImp.unsafePerformIO (IO H3Error -> H3Error) -> IO H3Error -> H3Error
forall a b. (a -> b) -> a -> b
$
  [Word64] -> ((Ptr CULong, CInt) -> IO H3Error) -> IO H3Error
forall b. [Word64] -> ((Ptr CULong, CInt) -> IO b) -> IO b
withH3IndexArray [Word64]
a1 (((Ptr CULong, CInt) -> IO H3Error) -> IO H3Error)
-> ((Ptr CULong, CInt) -> IO H3Error) -> IO H3Error
forall a b. (a -> b) -> a -> b
$ \(Ptr CULong
a1'1, CInt
a1'2) -> 
  LinkedGeoPolygonFPtr
-> (Ptr CLinkedGeoPolygon -> IO H3Error) -> IO H3Error
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
C2HSImp.withForeignPtr LinkedGeoPolygonFPtr
a2 ((Ptr CLinkedGeoPolygon -> IO H3Error) -> IO H3Error)
-> (Ptr CLinkedGeoPolygon -> IO H3Error) -> IO H3Error
forall a b. (a -> b) -> a -> b
$ \Ptr CLinkedGeoPolygon
a2' -> 
  Ptr CULong -> CInt -> Ptr CLinkedGeoPolygon -> IO CUInt
c2hs_cellsToLinkedMultiPolygon'_ Ptr CULong
a1'1  CInt
a1'2 Ptr CLinkedGeoPolygon
a2' IO CUInt -> (CUInt -> IO H3Error) -> IO H3Error
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CUInt
res ->
  let {res' :: H3Error
res' = CUInt -> H3Error
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
res} in
  H3Error -> IO H3Error
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (H3Error
res')
{-# LINE 365 "src/H3/Internal/H3Api.chs" #-}
hsCellsToLinkedMultiPolygon :: [H3Index] -> (H3Error, [GeoPolygon])
hsCellsToLinkedMultiPolygon h3indexs = unsafePerformIO $ do
  fptr <- mallocForeignPtr
  addForeignPtrFinalizer destroyLinkedMultiPolygon fptr 
  let h3error = c2hs_cellsToLinkedMultiPolygon h3indexs fptr
  if h3error == 0
  then do
    polys <- withForeignPtr fptr extractGeoPolygons
    return (h3error, polys)
  else return (h3error, [])
peekDouble :: Ptr CDouble -> IO Double
peekDouble :: Ptr CDouble -> IO Double
peekDouble Ptr CDouble
ptr = CDouble -> Double
cdoubleToDouble (CDouble -> Double) -> IO CDouble -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
ptr
  where cdoubleToDouble :: CDouble -> Double
cdoubleToDouble (CDouble Double
x) = Double
x
peekInt64 :: Ptr CLong -> IO Int64
peekInt64 :: Ptr CLong -> IO Int64
peekInt64 Ptr CLong
ptr = CLong -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CLong -> Int64) -> IO CLong -> IO Int64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CLong -> IO CLong
forall a. Storable a => Ptr a -> IO a
peek Ptr CLong
ptr
c2hs_getHexagonAreaAvgKm2 :: (Int) -> ((H3Error), (Double))
c2hs_getHexagonAreaAvgKm2 :: Int -> (H3Error, Double)
c2hs_getHexagonAreaAvgKm2 Int
a1 =
  IO (H3Error, Double) -> (H3Error, Double)
forall a. IO a -> a
C2HSImp.unsafePerformIO (IO (H3Error, Double) -> (H3Error, Double))
-> IO (H3Error, Double) -> (H3Error, Double)
forall a b. (a -> b) -> a -> b
$
  let {a1' :: CInt
a1' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a1} in 
  (Ptr CDouble -> IO (H3Error, Double)) -> IO (H3Error, Double)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CDouble -> IO (H3Error, Double)) -> IO (H3Error, Double))
-> (Ptr CDouble -> IO (H3Error, Double)) -> IO (H3Error, Double)
forall a b. (a -> b) -> a -> b
$ \Ptr CDouble
a2' -> 
  CInt -> Ptr CDouble -> IO CUInt
c2hs_getHexagonAreaAvgKm2'_ CInt
a1' Ptr CDouble
a2' IO CUInt -> (CUInt -> IO (H3Error, Double)) -> IO (H3Error, Double)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CUInt
res ->
  let {res' :: H3Error
res' = CUInt -> H3Error
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
res} in
  Ptr CDouble -> IO Double
peekDouble  Ptr CDouble
a2'IO Double
-> (Double -> IO (H3Error, Double)) -> IO (H3Error, Double)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a2'' -> 
  return (res', a2'')
{-# LINE 392 "src/H3/Internal/H3Api.chs" #-}
c2hs_getHexagonAreaAvgM2 :: (Int) -> ((H3Error), (Double))
c2hs_getHexagonAreaAvgM2 a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_getHexagonAreaAvgM2'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekDouble  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 397 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellAreaRads2 :: (H3Index) -> ((H3Error), (Double))
c2hs_cellAreaRads2 a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_cellAreaRads2'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekDouble  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 402 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellAreaKm2 :: (H3Index) -> ((H3Error), (Double))
c2hs_cellAreaKm2 a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_cellAreaKm2'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekDouble  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 407 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellAreaM2 :: (H3Index) -> ((H3Error), (Double))
c2hs_cellAreaM2 a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_cellAreaM2'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekDouble  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 412 "src/H3/Internal/H3Api.chs" #-}
c2hs_getHexagonEdgeLengthAvgKm :: (Int) -> ((H3Error), (Double))
c2hs_getHexagonEdgeLengthAvgKm a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_getHexagonEdgeLengthAvgKm'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekDouble  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 417 "src/H3/Internal/H3Api.chs" #-}
c2hs_getHexagonEdgeLengthAvgM :: (Int) -> ((H3Error), (Double))
c2hs_getHexagonEdgeLengthAvgM a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_getHexagonEdgeLengthAvgM'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekDouble  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 422 "src/H3/Internal/H3Api.chs" #-}
c2hs_edgeLengthRads :: (H3Index) -> ((H3Error), (Double))
c2hs_edgeLengthRads a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_edgeLengthRads'_ a1' a2' >>= \res :: CUInt
res ->
  let {res' :: H3Error
res' = CUInt -> H3Error
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
res} in
  Ptr CDouble -> IO Double
peekDouble  a2'IO Double
-> (Double -> IO (H3Error, Double)) -> IO (H3Error, Double)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a2'' -> 
  return (res', a2'')
{-# LINE 427 "src/H3/Internal/H3Api.chs" #-}
c2hs_edgeLengthKm :: (H3Index) -> ((H3Error), (Double))
c2hs_edgeLengthKm a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_edgeLengthKm'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekDouble  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 432 "src/H3/Internal/H3Api.chs" #-}
c2hs_edgeLengthM :: (H3Index) -> ((H3Error), (Double))
c2hs_edgeLengthM a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_edgeLengthM'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekDouble  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 437 "src/H3/Internal/H3Api.chs" #-}
c2hs_getNumCells :: (Int) -> ((H3Error), (Int64))
c2hs_getNumCells a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_getNumCells'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekInt64  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 442 "src/H3/Internal/H3Api.chs" #-}
greatCircleDistanceKm :: (LatLng) -> (LatLng) -> (Double)
greatCircleDistanceKm a1 a2 =
  C2HSImp.unsafePerformIO $
  with a1 $ \a1' -> 
  with a2 $ \a2' -> 
  greatCircleDistanceKm'_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 448 "src/H3/Internal/H3Api.chs" #-}
greatCircleDistanceM :: (LatLng) -> (LatLng) -> (Double)
greatCircleDistanceM a1 a2 =
  C2HSImp.unsafePerformIO $
  with a1 $ \a1' -> 
  with a2 $ \a2' -> 
  greatCircleDistanceM'_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 454 "src/H3/Internal/H3Api.chs" #-}
greatCircleDistanceRads :: (LatLng) -> (LatLng) -> (Double)
greatCircleDistanceRads a1 a2 =
  C2HSImp.unsafePerformIO $
  with a1 $ \a1' -> 
  with a2 $ \a2' -> 
  greatCircleDistanceRads'_ a1' a2' >>= \res ->
  let {res' = realToFrac res} in
  return (res')
{-# LINE 460 "src/H3/Internal/H3Api.chs" #-}
c2hs_gridDistance :: (H3Index) -> (H3Index) -> ((H3Error), (Int64))
c2hs_gridDistance :: Word64 -> Word64 -> (H3Error, Int64)
c2hs_gridDistance Word64
a1 Word64
a2 =
  IO (H3Error, Int64) -> (H3Error, Int64)
forall a. IO a -> a
C2HSImp.unsafePerformIO (IO (H3Error, Int64) -> (H3Error, Int64))
-> IO (H3Error, Int64) -> (H3Error, Int64)
forall a b. (a -> b) -> a -> b
$
  let {a1' :: CULong
a1' = Word64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
a1} in 
  let {a2' :: CULong
a2' = Word64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
a2} in 
  (Ptr CLong -> IO (H3Error, Int64)) -> IO (H3Error, Int64)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CLong -> IO (H3Error, Int64)) -> IO (H3Error, Int64))
-> (Ptr CLong -> IO (H3Error, Int64)) -> IO (H3Error, Int64)
forall a b. (a -> b) -> a -> b
$ \Ptr CLong
a3' -> 
  CULong -> CULong -> Ptr CLong -> IO CUInt
c2hs_gridDistance'_ CULong
a1' CULong
a2' Ptr CLong
a3' IO CUInt -> (CUInt -> IO (H3Error, Int64)) -> IO (H3Error, Int64)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CUInt
res ->
  let {res' :: H3Error
res' = CUInt -> H3Error
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
res} in
  Ptr CLong -> IO Int64
peekInt64  Ptr CLong
a3'IO Int64 -> (Int64 -> IO (H3Error, Int64)) -> IO (H3Error, Int64)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int64
a3'' -> 
  (H3Error, Int64) -> IO (H3Error, Int64)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (H3Error
res', Int64
a3'')
{-# LINE 470 "src/H3/Internal/H3Api.chs" #-}
data CoordIJ = CoordIJ Int Int
  deriving (Eq, Show)
instance Storable CoordIJ where
    sizeOf _ = 8
{-# LINE 477 "src/H3/Internal/H3Api.chs" #-}
    alignment _ = 4
{-# LINE 478 "src/H3/Internal/H3Api.chs" #-}
    peek p = do
      _i <- fromIntegral <$> (\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO C2HSImp.CInt}) p
      _j <- fromIntegral <$> (\ptr -> do {C2HSImp.peekByteOff ptr 4 :: IO C2HSImp.CInt}) p
      return $ CoordIJ _i _j
    poke p (CoordIJ _i _j) = do
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: C2HSImp.CInt)}) p (fromIntegral _i)
        (\ptr val -> do {C2HSImp.pokeByteOff ptr 4 (val :: C2HSImp.CInt)}) p (fromIntegral _j)
type CoordIJPtr = C2HSImp.Ptr (CoordIJ)
{-# LINE 488 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellToLocalIj :: (H3Index) -> (H3Index) -> (Word32) -> ((H3Error), (CoordIJ))
c2hs_cellToLocalIj :: Word64 -> Word64 -> H3Error -> (H3Error, CoordIJ)
c2hs_cellToLocalIj Word64
a1 Word64
a2 H3Error
a3 =
  IO (H3Error, CoordIJ) -> (H3Error, CoordIJ)
forall a. IO a -> a
C2HSImp.unsafePerformIO (IO (H3Error, CoordIJ) -> (H3Error, CoordIJ))
-> IO (H3Error, CoordIJ) -> (H3Error, CoordIJ)
forall a b. (a -> b) -> a -> b
$
  let {a1' :: CULong
a1' = Word64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
a1} in 
  let {a2' :: CULong
a2' = Word64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
a2} in 
  let {a3' :: CUInt
a3' = H3Error -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral H3Error
a3} in 
  (Ptr CoordIJ -> IO (H3Error, CoordIJ)) -> IO (H3Error, CoordIJ)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CoordIJ -> IO (H3Error, CoordIJ)) -> IO (H3Error, CoordIJ))
-> (Ptr CoordIJ -> IO (H3Error, CoordIJ)) -> IO (H3Error, CoordIJ)
forall a b. (a -> b) -> a -> b
$ \Ptr CoordIJ
a4' -> 
  CULong -> CULong -> CUInt -> Ptr CoordIJ -> IO CUInt
c2hs_cellToLocalIj'_ CULong
a1' CULong
a2' CUInt
a3' Ptr CoordIJ
a4' IO CUInt
-> (CUInt -> IO (H3Error, CoordIJ)) -> IO (H3Error, CoordIJ)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CUInt
res ->
  let {res' :: H3Error
res' = CUInt -> H3Error
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
res} in
  Ptr CoordIJ -> IO CoordIJ
forall a. Storable a => Ptr a -> IO a
peek  Ptr CoordIJ
a4'IO CoordIJ
-> (CoordIJ -> IO (H3Error, CoordIJ)) -> IO (H3Error, CoordIJ)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CoordIJ
a4'' -> 
  (H3Error, CoordIJ) -> IO (H3Error, CoordIJ)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (H3Error
res', CoordIJ
a4'')
{-# LINE 495 "src/H3/Internal/H3Api.chs" #-}
c2hs_localIjToCell :: (H3Index) -> (CoordIJ) -> (Word32) -> ((H3Error), (H3Index))
c2hs_localIjToCell a1 a2 a3 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  with a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  alloca $ \a4' -> 
  c2hs_localIjToCell'_ a1' a2' a3' a4' >>= \res ->
  let {res' = fromIntegral res} in
  peekH3Index  a4'>>= \a4'' -> 
  return (res', a4'')
{-# LINE 502 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellToParent :: (H3Index) -> (Int) -> ((H3Error), (H3Index))
c2hs_cellToParent a1 a2 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  c2hs_cellToParent'_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  peekH3Index  a3'>>= \a3'' -> 
  return (res', a3'')
{-# LINE 512 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellToCenterChild :: (H3Index) -> (Int) -> ((H3Error), (H3Index))
c2hs_cellToCenterChild a1 a2 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  c2hs_cellToCenterChild'_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  peekH3Index  a3'>>= \a3'' -> 
  return (res', a3'')
{-# LINE 518 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellToChildPos :: (H3Index) -> (Int) -> ((H3Error), (Int64))
c2hs_cellToChildPos a1 a2 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  c2hs_cellToChildPos'_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  peekInt64  a3'>>= \a3'' -> 
  return (res', a3'')
{-# LINE 524 "src/H3/Internal/H3Api.chs" #-}
c2hs_childPosToCell :: (Int64) -> (H3Index) -> (Int) -> ((H3Error), (H3Index))
c2hs_childPosToCell a1 a2 a3 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  alloca $ \a4' -> 
  c2hs_childPosToCell'_ a1' a2' a3' a4' >>= \res ->
  let {res' = fromIntegral res} in
  peekH3Index  a4'>>= \a4'' -> 
  return (res', a4'')
peekBool :: Ptr CInt -> IO Bool
{-# LINE 531 "src/H3/Internal/H3Api.chs" #-}
peekBool :: Ptr CInt -> IO Bool
peekBool intPtr = (/=0) <$> peek intPtr
c2hs_areNeighborCells :: (H3Index) -> (H3Index) -> ((H3Error), (Bool))
c2hs_areNeighborCells :: Word64 -> Word64 -> (H3Error, Bool)
c2hs_areNeighborCells Word64
a1 Word64
a2 =
  IO (H3Error, Bool) -> (H3Error, Bool)
forall a. IO a -> a
C2HSImp.unsafePerformIO (IO (H3Error, Bool) -> (H3Error, Bool))
-> IO (H3Error, Bool) -> (H3Error, Bool)
forall a b. (a -> b) -> a -> b
$
  let {a1' :: CULong
a1' = Word64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
a1} in 
  let {a2' :: CULong
a2' = Word64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
a2} in 
  (Ptr CInt -> IO (H3Error, Bool)) -> IO (H3Error, Bool)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (H3Error, Bool)) -> IO (H3Error, Bool))
-> (Ptr CInt -> IO (H3Error, Bool)) -> IO (H3Error, Bool)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
a3' -> 
  CULong -> CULong -> Ptr CInt -> IO CUInt
c2hs_areNeighborCells'_ CULong
a1' CULong
a2' Ptr CInt
a3' IO CUInt -> (CUInt -> IO (H3Error, Bool)) -> IO (H3Error, Bool)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CUInt
res ->
  let {res' :: H3Error
res' = CUInt -> H3Error
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
res} in
  Ptr CInt -> IO Bool
peekBool  Ptr CInt
a3'IO Bool -> (Bool -> IO (H3Error, Bool)) -> IO (H3Error, Bool)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
a3'' -> 
  (H3Error, Bool) -> IO (H3Error, Bool)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (H3Error
res', Bool
a3'')
{-# LINE 544 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellsToDirectedEdge :: (H3Index) -> (H3Index) -> ((H3Error), (H3Index))
c2hs_cellsToDirectedEdge a1 a2 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  c2hs_cellsToDirectedEdge'_ a1' a2' a3' >>= \res ->
  let {res' = fromIntegral res} in
  peekH3Index  a3'>>= \a3'' -> 
  return (res', a3'')
{-# LINE 550 "src/H3/Internal/H3Api.chs" #-}
c2hs_getDirectedEdgeOrigin :: (H3Index) -> ((H3Error), (H3Index))
c2hs_getDirectedEdgeOrigin a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_getDirectedEdgeOrigin'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekH3Index  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 555 "src/H3/Internal/H3Api.chs" #-}
c2hs_getDirectedEdgeDestination :: (H3Index) -> ((H3Error), (H3Index))
c2hs_getDirectedEdgeDestination a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_getDirectedEdgeDestination'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peekH3Index  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 560 "src/H3/Internal/H3Api.chs" #-}
c2hs_directedEdgeToBoundary :: (H3Index) -> ((H3Error), ([LatLng]))
c2hs_directedEdgeToBoundary a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  withPlaceholderCellBoundary $ \a2' -> 
  c2hs_directedEdgeToBoundary'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  cellBoundaryToLatLngs  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 565 "src/H3/Internal/H3Api.chs" #-}
c2hs_cellToVertex :: (H3Index) -> (Int) -> ((H3Error), (H3Index))
c2hs_cellToVertex :: Word64 -> Int -> (H3Error, Word64)
c2hs_cellToVertex Word64
a1 Int
a2 =
  IO (H3Error, Word64) -> (H3Error, Word64)
forall a. IO a -> a
C2HSImp.unsafePerformIO (IO (H3Error, Word64) -> (H3Error, Word64))
-> IO (H3Error, Word64) -> (H3Error, Word64)
forall a b. (a -> b) -> a -> b
$
  let {a1' :: CULong
a1' = Word64 -> CULong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
a1} in 
  let {a2' :: CInt
a2' = Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a2} in 
  (Ptr CULong -> IO (H3Error, Word64)) -> IO (H3Error, Word64)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CULong -> IO (H3Error, Word64)) -> IO (H3Error, Word64))
-> (Ptr CULong -> IO (H3Error, Word64)) -> IO (H3Error, Word64)
forall a b. (a -> b) -> a -> b
$ \Ptr CULong
a3' -> 
  CULong -> CInt -> Ptr CULong -> IO CUInt
c2hs_cellToVertex'_ CULong
a1' CInt
a2' Ptr CULong
a3' IO CUInt -> (CUInt -> IO (H3Error, Word64)) -> IO (H3Error, Word64)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CUInt
res ->
  let {res' :: H3Error
res' = CUInt -> H3Error
forall a b. (Integral a, Num b) => a -> b
fromIntegral CUInt
res} in
  Ptr CULong -> IO Word64
peekH3Index  Ptr CULong
a3'IO Word64
-> (Word64 -> IO (H3Error, Word64)) -> IO (H3Error, Word64)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Word64
a3'' -> 
  (H3Error, Word64) -> IO (H3Error, Word64)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (H3Error
res', Word64
a3'')
{-# LINE 575 "src/H3/Internal/H3Api.chs" #-}
c2hs_vertexToLatLng :: (H3Index) -> ((H3Error), (LatLng))
c2hs_vertexToLatLng a1 =
  C2HSImp.unsafePerformIO $
  let {a1' = fromIntegral a1} in 
  alloca $ \a2' -> 
  c2hs_vertexToLatLng'_ a1' a2' >>= \res ->
  let {res' = fromIntegral res} in
  peek  a2'>>= \a2'' -> 
  return (res', a2'')
{-# LINE 580 "src/H3/Internal/H3Api.chs" #-}
foreign import ccall safe "H3/Internal/H3Api.chs.h latLngToCell"
  c2hs_latLngToCell'_ :: ((LatLngPtr) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CUInt))))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellToLatLng"
  c2hs_cellToLatLng'_ :: (C2HSImp.CULong -> ((LatLngPtr) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellToBoundary"
  c2hs_cellToBoundary'_ :: (C2HSImp.CULong -> ((CellBoundaryPtr) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h h3ToString"
  c2hs_h3ToString'_ :: (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CULong -> (IO C2HSImp.CUInt))))
foreign import ccall safe "H3/Internal/H3Api.chs.h stringToH3"
  c2hs_stringToH3'_ :: ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellsToLinkedMultiPolygon"
  c2hs_cellsToLinkedMultiPolygon'_ :: ((C2HSImp.Ptr C2HSImp.CULong) -> (C2HSImp.CInt -> ((C2HSImp.Ptr (CLinkedGeoPolygon)) -> (IO C2HSImp.CUInt))))
foreign import ccall safe "H3/Internal/H3Api.chs.h getHexagonAreaAvgKm2"
  c2hs_getHexagonAreaAvgKm2'_ :: (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h getHexagonAreaAvgM2"
  c2hs_getHexagonAreaAvgM2'_ :: (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellAreaRads2"
  c2hs_cellAreaRads2'_ :: (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellAreaKm2"
  c2hs_cellAreaKm2'_ :: (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellAreaM2"
  c2hs_cellAreaM2'_ :: (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h getHexagonEdgeLengthAvgKm"
  c2hs_getHexagonEdgeLengthAvgKm'_ :: (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h getHexagonEdgeLengthAvgM"
  c2hs_getHexagonEdgeLengthAvgM'_ :: (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h edgeLengthRads"
  c2hs_edgeLengthRads'_ :: (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h edgeLengthKm"
  c2hs_edgeLengthKm'_ :: (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h edgeLengthM"
  c2hs_edgeLengthM'_ :: (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CDouble) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h getNumCells"
  c2hs_getNumCells'_ :: (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CLong) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h greatCircleDistanceKm"
  greatCircleDistanceKm'_ :: ((LatLngPtr) -> ((LatLngPtr) -> (IO C2HSImp.CDouble)))
foreign import ccall safe "H3/Internal/H3Api.chs.h greatCircleDistanceM"
  greatCircleDistanceM'_ :: ((LatLngPtr) -> ((LatLngPtr) -> (IO C2HSImp.CDouble)))
foreign import ccall safe "H3/Internal/H3Api.chs.h greatCircleDistanceRads"
  greatCircleDistanceRads'_ :: ((LatLngPtr) -> ((LatLngPtr) -> (IO C2HSImp.CDouble)))
foreign import ccall safe "H3/Internal/H3Api.chs.h gridDistance"
  c2hs_gridDistance'_ :: (C2HSImp.CULong -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CLong) -> (IO C2HSImp.CUInt))))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellToLocalIj"
  c2hs_cellToLocalIj'_ :: (C2HSImp.CULong -> (C2HSImp.CULong -> (C2HSImp.CUInt -> ((CoordIJPtr) -> (IO C2HSImp.CUInt)))))
foreign import ccall safe "H3/Internal/H3Api.chs.h localIjToCell"
  c2hs_localIjToCell'_ :: (C2HSImp.CULong -> ((CoordIJPtr) -> (C2HSImp.CUInt -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CUInt)))))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellToParent"
  c2hs_cellToParent'_ :: (C2HSImp.CULong -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CUInt))))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellToCenterChild"
  c2hs_cellToCenterChild'_ :: (C2HSImp.CULong -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CUInt))))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellToChildPos"
  c2hs_cellToChildPos'_ :: (C2HSImp.CULong -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CLong) -> (IO C2HSImp.CUInt))))
foreign import ccall safe "H3/Internal/H3Api.chs.h childPosToCell"
  c2hs_childPosToCell'_ :: (C2HSImp.CLong -> (C2HSImp.CULong -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CUInt)))))
foreign import ccall safe "H3/Internal/H3Api.chs.h areNeighborCells"
  c2hs_areNeighborCells'_ :: (C2HSImp.CULong -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CInt) -> (IO C2HSImp.CUInt))))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellsToDirectedEdge"
  c2hs_cellsToDirectedEdge'_ :: (C2HSImp.CULong -> (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CUInt))))
foreign import ccall safe "H3/Internal/H3Api.chs.h getDirectedEdgeOrigin"
  c2hs_getDirectedEdgeOrigin'_ :: (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h getDirectedEdgeDestination"
  c2hs_getDirectedEdgeDestination'_ :: (C2HSImp.CULong -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h directedEdgeToBoundary"
  c2hs_directedEdgeToBoundary'_ :: (C2HSImp.CULong -> ((CellBoundaryPtr) -> (IO C2HSImp.CUInt)))
foreign import ccall safe "H3/Internal/H3Api.chs.h cellToVertex"
  c2hs_cellToVertex'_ :: (C2HSImp.CULong -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CULong) -> (IO C2HSImp.CUInt))))
foreign import ccall safe "H3/Internal/H3Api.chs.h vertexToLatLng"
  c2hs_vertexToLatLng'_ :: (C2HSImp.CULong -> ((LatLngPtr) -> (IO C2HSImp.CUInt)))