{-# LINE 1 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}

{-# LINE 2 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}

{-# LINE 3 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}

-- | <http://gts.sourceforge.net/reference/gts-delaunay-and-constrained-delaunay-triangulations.html>

module Bindings.Gts.SurfaceOperations.DelaunayAndConstrainedDelaunayTriangulations where
import Bindings.GLib
import Bindings.Gts.Types
import Foreign.Ptr (Ptr,FunPtr,plusPtr)
import Foreign.Ptr (wordPtrToPtr,castPtrToFunPtr)
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String (CString,CStringLen,CWString,CWStringLen)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word

{-# LINE 10 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}

foreign import ccall "inline_GTS_CONSTRAINT_CLASS" c'GTS_CONSTRAINT_CLASS
  :: Ptr a -> Ptr C'GtsConstraintClass

{-# LINE 12 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "inline_GTS_CONSTRAINT" c'GTS_CONSTRAINT
  :: Ptr a -> Ptr C'GtsConstraint

{-# LINE 13 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "inline_GTS_IS_CONSTRAINT" c'GTS_IS_CONSTRAINT
  :: Ptr a -> Ptr C'gboolean

{-# LINE 14 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}

foreign import ccall "gts_constraint_class" c'gts_constraint_class
  :: IO (Ptr C'GtsConstraintClass)
foreign import ccall "&gts_constraint_class" p'gts_constraint_class
  :: FunPtr (IO (Ptr C'GtsConstraintClass))

{-# LINE 16 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "gts_point_locate" c'gts_point_locate
  :: Ptr C'GtsPoint -> Ptr C'GtsSurface -> Ptr C'GtsFace -> IO (Ptr C'GtsFace)
foreign import ccall "&gts_point_locate" p'gts_point_locate
  :: FunPtr (Ptr C'GtsPoint -> Ptr C'GtsSurface -> Ptr C'GtsFace -> IO (Ptr C'GtsFace))

{-# LINE 17 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "gts_delaunay_add_vertex" c'gts_delaunay_add_vertex
  :: Ptr C'GtsSurface -> Ptr C'GtsVertex -> Ptr C'GtsFace -> IO (Ptr C'GtsVertex)
foreign import ccall "&gts_delaunay_add_vertex" p'gts_delaunay_add_vertex
  :: FunPtr (Ptr C'GtsSurface -> Ptr C'GtsVertex -> Ptr C'GtsFace -> IO (Ptr C'GtsVertex))

{-# LINE 18 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "gts_delaunay_add_vertex_to_face" c'gts_delaunay_add_vertex_to_face
  :: Ptr C'GtsSurface -> Ptr C'GtsVertex -> Ptr C'GtsFace -> IO (Ptr C'GtsVertex)
foreign import ccall "&gts_delaunay_add_vertex_to_face" p'gts_delaunay_add_vertex_to_face
  :: FunPtr (Ptr C'GtsSurface -> Ptr C'GtsVertex -> Ptr C'GtsFace -> IO (Ptr C'GtsVertex))

{-# LINE 19 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "gts_delaunay_remove_vertex" c'gts_delaunay_remove_vertex
  :: Ptr C'GtsSurface -> Ptr C'GtsVertex -> IO ()
foreign import ccall "&gts_delaunay_remove_vertex" p'gts_delaunay_remove_vertex
  :: FunPtr (Ptr C'GtsSurface -> Ptr C'GtsVertex -> IO ())

{-# LINE 20 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "gts_delaunay_add_constraint" c'gts_delaunay_add_constraint
  :: Ptr C'GtsSurface -> Ptr C'GtsConstraint -> IO (Ptr C'GSList)
foreign import ccall "&gts_delaunay_add_constraint" p'gts_delaunay_add_constraint
  :: FunPtr (Ptr C'GtsSurface -> Ptr C'GtsConstraint -> IO (Ptr C'GSList))

{-# LINE 21 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "gts_delaunay_check" c'gts_delaunay_check
  :: Ptr C'GtsSurface -> IO (Ptr C'GtsFace)
foreign import ccall "&gts_delaunay_check" p'gts_delaunay_check
  :: FunPtr (Ptr C'GtsSurface -> IO (Ptr C'GtsFace))

{-# LINE 22 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "gts_delaunay_remove_hull" c'gts_delaunay_remove_hull
  :: Ptr C'GtsSurface -> IO ()
foreign import ccall "&gts_delaunay_remove_hull" p'gts_delaunay_remove_hull
  :: FunPtr (Ptr C'GtsSurface -> IO ())

{-# LINE 23 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "gts_delaunay_conform" c'gts_delaunay_conform
  :: Ptr C'GtsSurface -> C'gint -> C'GtsEncroachFunc -> C'gpointer -> IO C'guint
foreign import ccall "&gts_delaunay_conform" p'gts_delaunay_conform
  :: FunPtr (Ptr C'GtsSurface -> C'gint -> C'GtsEncroachFunc -> C'gpointer -> IO C'guint)

{-# LINE 24 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}
foreign import ccall "gts_delaunay_refine" c'gts_delaunay_refine
  :: Ptr C'GtsSurface -> C'gint -> C'GtsEncroachFunc -> C'gpointer -> C'GtsKeyFunc -> C'gpointer -> IO C'guint
foreign import ccall "&gts_delaunay_refine" p'gts_delaunay_refine
  :: FunPtr (Ptr C'GtsSurface -> C'gint -> C'GtsEncroachFunc -> C'gpointer -> C'GtsKeyFunc -> C'gpointer -> IO C'guint)

{-# LINE 25 "src/Bindings/Gts/SurfaceOperations/DelaunayAndConstrainedDelaunayTriangulations.hsc" #-}