{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-} module GDAL.OGRCurvePolygon.FFI where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import GDAL.OGRCurvePolygon.RawType import GDAL.OGRCurvePolygon.RawType import GDAL.OGRGeometry.RawType import GDAL.OGRPolygon.RawType import GDAL.OGRMultiPolygon.RawType import GDAL.OGREnvelope.RawType import GDAL.OGRPoint.RawType foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_getGeometryType" c_ogrcurvepolygon_getgeometrytype :: Ptr RawOGRCurvePolygon -> IO CUInt foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_getEnvelope" c_ogrcurvepolygon_getenvelope :: Ptr RawOGRCurvePolygon -> Ptr RawOGREnvelope -> IO () foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Intersects" c_ogrcurvepolygon_intersects :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Equals" c_ogrcurvepolygon_equals :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Disjoint" c_ogrcurvepolygon_disjoint :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Touches" c_ogrcurvepolygon_touches :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Crosses" c_ogrcurvepolygon_crosses :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Within" c_ogrcurvepolygon_within :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Contains" c_ogrcurvepolygon_contains :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Overlaps" c_ogrcurvepolygon_overlaps :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Boundary" c_ogrcurvepolygon_boundary :: Ptr RawOGRCurvePolygon -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Distance" c_ogrcurvepolygon_distance :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO CDouble foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_ConvexHull" c_ogrcurvepolygon_convexhull :: Ptr RawOGRCurvePolygon -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Buffer" c_ogrcurvepolygon_buffer :: Ptr RawOGRCurvePolygon -> CDouble -> CInt -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Intersection" c_ogrcurvepolygon_intersection :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Union" c_ogrcurvepolygon_union :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_UnionCascaded" c_ogrcurvepolygon_unioncascaded :: Ptr RawOGRCurvePolygon -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Difference" c_ogrcurvepolygon_difference :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_SymDifference" c_ogrcurvepolygon_symdifference :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Centroid" c_ogrcurvepolygon_centroid :: Ptr RawOGRCurvePolygon -> Ptr RawOGRPoint -> IO CInt foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Simplify" c_ogrcurvepolygon_simplify :: Ptr RawOGRCurvePolygon -> CDouble -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_DelaunayTriangulation" c_ogrcurvepolygon_delaunaytriangulation :: Ptr RawOGRCurvePolygon -> CDouble -> CInt -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Polygonize" c_ogrcurvepolygon_polygonize :: Ptr RawOGRCurvePolygon -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_Distance3D" c_ogrcurvepolygon_distance3d :: Ptr RawOGRCurvePolygon -> Ptr RawOGRGeometry -> IO CDouble foreign import ccall interruptible "HGDALOGRCurvePolygon.h OGRCurvePolygon_delete" c_ogrcurvepolygon_delete :: Ptr RawOGRCurvePolygon -> IO ()