{-# LINE 1 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}

{-# LINE 2 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}

{-# LINE 3 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}

-- | <http://gts.sourceforge.net/reference/gts-extended-binary-heaps.html>

module Bindings.Gts.BasicMacrosFunctionsAndDataStructures.ExtendedBinaryHeaps 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/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}

foreign import ccall "gts_eheap_new" c'gts_eheap_new
  :: C'GtsKeyFunc -> C'gpointer -> IO (Ptr C'GtsEHeap)
foreign import ccall "&gts_eheap_new" p'gts_eheap_new
  :: FunPtr (C'GtsKeyFunc -> C'gpointer -> IO (Ptr C'GtsEHeap))

{-# LINE 12 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_insert" c'gts_eheap_insert
  :: Ptr C'GtsEHeap -> C'gpointer -> IO (Ptr C'GtsEHeapPair)
foreign import ccall "&gts_eheap_insert" p'gts_eheap_insert
  :: FunPtr (Ptr C'GtsEHeap -> C'gpointer -> IO (Ptr C'GtsEHeapPair))

{-# LINE 13 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_insert_with_key" c'gts_eheap_insert_with_key
  :: Ptr C'GtsEHeap -> C'gpointer -> C'gdouble -> IO (Ptr C'GtsEHeapPair)
foreign import ccall "&gts_eheap_insert_with_key" p'gts_eheap_insert_with_key
  :: FunPtr (Ptr C'GtsEHeap -> C'gpointer -> C'gdouble -> IO (Ptr C'GtsEHeapPair))

{-# LINE 14 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_top" c'gts_eheap_top
  :: Ptr C'GtsEHeap -> Ptr C'gdouble -> IO C'gpointer
foreign import ccall "&gts_eheap_top" p'gts_eheap_top
  :: FunPtr (Ptr C'GtsEHeap -> Ptr C'gdouble -> IO C'gpointer)

{-# LINE 15 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_remove_top" c'gts_eheap_remove_top
  :: Ptr C'GtsEHeap -> Ptr C'gdouble -> IO C'gpointer
foreign import ccall "&gts_eheap_remove_top" p'gts_eheap_remove_top
  :: FunPtr (Ptr C'GtsEHeap -> Ptr C'gdouble -> IO C'gpointer)

{-# LINE 16 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_remove" c'gts_eheap_remove
  :: Ptr C'GtsEHeap -> Ptr C'GtsEHeapPair -> IO C'gpointer
foreign import ccall "&gts_eheap_remove" p'gts_eheap_remove
  :: FunPtr (Ptr C'GtsEHeap -> Ptr C'GtsEHeapPair -> IO C'gpointer)

{-# LINE 17 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_decrease_key" c'gts_eheap_decrease_key
  :: Ptr C'GtsEHeap -> Ptr C'GtsEHeapPair -> C'gdouble -> IO ()
foreign import ccall "&gts_eheap_decrease_key" p'gts_eheap_decrease_key
  :: FunPtr (Ptr C'GtsEHeap -> Ptr C'GtsEHeapPair -> C'gdouble -> IO ())

{-# LINE 18 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_key" c'gts_eheap_key
  :: Ptr C'GtsEHeap -> C'gpointer -> IO C'gdouble
foreign import ccall "&gts_eheap_key" p'gts_eheap_key
  :: FunPtr (Ptr C'GtsEHeap -> C'gpointer -> IO C'gdouble)

{-# LINE 19 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_randomized" c'gts_eheap_randomized
  :: Ptr C'GtsEHeap -> C'gboolean -> IO ()
foreign import ccall "&gts_eheap_randomized" p'gts_eheap_randomized
  :: FunPtr (Ptr C'GtsEHeap -> C'gboolean -> IO ())

{-# LINE 20 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_update" c'gts_eheap_update
  :: Ptr C'GtsEHeap -> IO ()
foreign import ccall "&gts_eheap_update" p'gts_eheap_update
  :: FunPtr (Ptr C'GtsEHeap -> IO ())

{-# LINE 21 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_freeze" c'gts_eheap_freeze
  :: Ptr C'GtsEHeap -> IO ()
foreign import ccall "&gts_eheap_freeze" p'gts_eheap_freeze
  :: FunPtr (Ptr C'GtsEHeap -> IO ())

{-# LINE 22 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_thaw" c'gts_eheap_thaw
  :: Ptr C'GtsEHeap -> IO ()
foreign import ccall "&gts_eheap_thaw" p'gts_eheap_thaw
  :: FunPtr (Ptr C'GtsEHeap -> IO ())

{-# LINE 23 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_foreach" c'gts_eheap_foreach
  :: Ptr C'GtsEHeap -> C'GFunc -> C'gpointer -> IO ()
foreign import ccall "&gts_eheap_foreach" p'gts_eheap_foreach
  :: FunPtr (Ptr C'GtsEHeap -> C'GFunc -> C'gpointer -> IO ())

{-# LINE 24 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_size" c'gts_eheap_size
  :: Ptr C'GtsEHeap -> IO C'guint
foreign import ccall "&gts_eheap_size" p'gts_eheap_size
  :: FunPtr (Ptr C'GtsEHeap -> IO C'guint)

{-# LINE 25 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}
foreign import ccall "gts_eheap_destroy" c'gts_eheap_destroy
  :: Ptr C'GtsEHeap -> IO ()
foreign import ccall "&gts_eheap_destroy" p'gts_eheap_destroy
  :: FunPtr (Ptr C'GtsEHeap -> IO ())

{-# LINE 26 "src/Bindings/Gts/BasicMacrosFunctionsAndDataStructures/ExtendedBinaryHeaps.hsc" #-}