{-# LINE 1 "src/GDAL/OGRPoint/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-}
module GDAL.OGRPoint.FFI where
import Data.Word
import Data.Int
import Foreign.C
import Foreign.Ptr
import GDAL.OGRPoint.RawType
import GDAL.OGRPoint.RawType
import GDAL.OGRGeometry.RawType
import GDAL.OGRPolygon.RawType
import GDAL.OGRMultiPolygon.RawType
import GDAL.OGREnvelope.RawType

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_getGeometryType"
               c_ogrpoint_getgeometrytype :: Ptr RawOGRPoint -> IO CUInt

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_getEnvelope" c_ogrpoint_getenvelope ::
               Ptr RawOGRPoint -> Ptr RawOGREnvelope -> IO ()

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Intersects" c_ogrpoint_intersects ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO CBool

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Equals" c_ogrpoint_equals ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO CBool

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Disjoint" c_ogrpoint_disjoint ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO CBool

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Touches" c_ogrpoint_touches ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO CBool

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Crosses" c_ogrpoint_crosses ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO CBool

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Within" c_ogrpoint_within ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO CBool

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Contains" c_ogrpoint_contains ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO CBool

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Overlaps" c_ogrpoint_overlaps ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO CBool

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Boundary" c_ogrpoint_boundary ::
               Ptr RawOGRPoint -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Distance" c_ogrpoint_distance ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO CDouble

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_ConvexHull" c_ogrpoint_convexhull ::
               Ptr RawOGRPoint -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Buffer" c_ogrpoint_buffer ::
               Ptr RawOGRPoint -> CDouble -> CInt -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Intersection" c_ogrpoint_intersection ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible "HGDALOGRPoint.h OGRPoint_Union"
               c_ogrpoint_union ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_UnionCascaded" c_ogrpoint_unioncascaded
               :: Ptr RawOGRPoint -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Difference" c_ogrpoint_difference ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_SymDifference" c_ogrpoint_symdifference
               :: Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Centroid" c_ogrpoint_centroid ::
               Ptr RawOGRPoint -> Ptr RawOGRPoint -> IO CInt

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Simplify" c_ogrpoint_simplify ::
               Ptr RawOGRPoint -> CDouble -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_DelaunayTriangulation"
               c_ogrpoint_delaunaytriangulation ::
               Ptr RawOGRPoint -> CDouble -> CInt -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Polygonize" c_ogrpoint_polygonize ::
               Ptr RawOGRPoint -> IO (Ptr RawOGRGeometry)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_Distance3D" c_ogrpoint_distance3d ::
               Ptr RawOGRPoint -> Ptr RawOGRGeometry -> IO CDouble

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_delete" c_ogrpoint_delete ::
               Ptr RawOGRPoint -> IO ()

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_newOGRPoint" c_ogrpoint_newogrpoint ::
               IO (Ptr RawOGRPoint)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_newOGRPoint2" c_ogrpoint_newogrpoint2 ::
               CDouble -> CDouble -> IO (Ptr RawOGRPoint)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_newOGRPoint3" c_ogrpoint_newogrpoint3 ::
               CDouble -> CDouble -> CDouble -> IO (Ptr RawOGRPoint)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_newOGRPoint4" c_ogrpoint_newogrpoint4 ::
               CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawOGRPoint)

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_oGRPoint_getX" c_ogrpoint_ogrpoint_getx
               :: Ptr RawOGRPoint -> IO CDouble

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_oGRPoint_getY" c_ogrpoint_ogrpoint_gety
               :: Ptr RawOGRPoint -> IO CDouble

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_oGRPoint_getZ" c_ogrpoint_ogrpoint_getz
               :: Ptr RawOGRPoint -> IO CDouble

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_oGRPoint_getM" c_ogrpoint_ogrpoint_getm
               :: Ptr RawOGRPoint -> IO CDouble

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_oGRPoint_setX" c_ogrpoint_ogrpoint_setx
               :: Ptr RawOGRPoint -> CDouble -> IO ()

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_oGRPoint_setY" c_ogrpoint_ogrpoint_sety
               :: Ptr RawOGRPoint -> CDouble -> IO ()

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_oGRPoint_setZ" c_ogrpoint_ogrpoint_setz
               :: Ptr RawOGRPoint -> CDouble -> IO ()

foreign import ccall interruptible
               "HGDALOGRPoint.h OGRPoint_oGRPoint_setM" c_ogrpoint_ogrpoint_setm
               :: Ptr RawOGRPoint -> CDouble -> IO ()