{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-} module GDAL.OGRSimpleCurve.FFI where import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import GDAL.OGRSimpleCurve.RawType import GDAL.OGRSimpleCurve.RawType import GDAL.OGRPointIterator.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 "HGDALOGRSimpleCurve.h OGRSimpleCurve_getNumPoints" c_ogrsimplecurve_getnumpoints :: Ptr RawOGRSimpleCurve -> IO CInt foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_getPointIterator" c_ogrsimplecurve_getpointiterator :: Ptr RawOGRSimpleCurve -> IO (Ptr RawOGRPointIterator) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_getGeometryType" c_ogrsimplecurve_getgeometrytype :: Ptr RawOGRSimpleCurve -> IO CUInt foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_getEnvelope" c_ogrsimplecurve_getenvelope :: Ptr RawOGRSimpleCurve -> Ptr RawOGREnvelope -> IO () foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Intersects" c_ogrsimplecurve_intersects :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Equals" c_ogrsimplecurve_equals :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Disjoint" c_ogrsimplecurve_disjoint :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Touches" c_ogrsimplecurve_touches :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Crosses" c_ogrsimplecurve_crosses :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Within" c_ogrsimplecurve_within :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Contains" c_ogrsimplecurve_contains :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Overlaps" c_ogrsimplecurve_overlaps :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO CBool foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Boundary" c_ogrsimplecurve_boundary :: Ptr RawOGRSimpleCurve -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Distance" c_ogrsimplecurve_distance :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO CDouble foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_ConvexHull" c_ogrsimplecurve_convexhull :: Ptr RawOGRSimpleCurve -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Buffer" c_ogrsimplecurve_buffer :: Ptr RawOGRSimpleCurve -> CDouble -> CInt -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Intersection" c_ogrsimplecurve_intersection :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Union" c_ogrsimplecurve_union :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_UnionCascaded" c_ogrsimplecurve_unioncascaded :: Ptr RawOGRSimpleCurve -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Difference" c_ogrsimplecurve_difference :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_SymDifference" c_ogrsimplecurve_symdifference :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Centroid" c_ogrsimplecurve_centroid :: Ptr RawOGRSimpleCurve -> Ptr RawOGRPoint -> IO CInt foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Simplify" c_ogrsimplecurve_simplify :: Ptr RawOGRSimpleCurve -> CDouble -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_DelaunayTriangulation" c_ogrsimplecurve_delaunaytriangulation :: Ptr RawOGRSimpleCurve -> CDouble -> CInt -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Polygonize" c_ogrsimplecurve_polygonize :: Ptr RawOGRSimpleCurve -> IO (Ptr RawOGRGeometry) foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_Distance3D" c_ogrsimplecurve_distance3d :: Ptr RawOGRSimpleCurve -> Ptr RawOGRGeometry -> IO CDouble foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_delete" c_ogrsimplecurve_delete :: Ptr RawOGRSimpleCurve -> IO () foreign import ccall interruptible "HGDALOGRSimpleCurve.h OGRSimpleCurve_oGRSimpleCurve_getPoints" c_ogrsimplecurve_ogrsimplecurve_getpoints :: Ptr RawOGRSimpleCurve -> Ptr () -> CInt -> Ptr () -> CInt -> Ptr () -> CInt -> IO ()