{-# LINE 1 "src/OGDF/FMMMLayout/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-}
module OGDF.FMMMLayout.FFI where
import Data.Word
import Data.Int
import Foreign.C
import Foreign.Ptr
import OGDF.FMMMLayout.RawType
import OGDF.FMMMLayout.RawType
import OGDF.GraphAttributes.RawType

foreign import ccall interruptible
               "OGDFFMMMLayout.h FMMMLayout_delete" c_fmmmlayout_delete ::
               Ptr RawFMMMLayout -> IO ()

foreign import ccall interruptible
               "OGDFFMMMLayout.h FMMMLayout_call" c_fmmmlayout_call ::
               Ptr RawFMMMLayout -> Ptr RawGraphAttributes -> IO ()

foreign import ccall interruptible
               "OGDFFMMMLayout.h FMMMLayout_newFMMMLayout"
               c_fmmmlayout_newfmmmlayout :: IO (Ptr RawFMMMLayout)

foreign import ccall interruptible
               "OGDFFMMMLayout.h FMMMLayout_fMMMLayout_useHighLevelOptions"
               c_fmmmlayout_fmmmlayout_usehighleveloptions ::
               Ptr RawFMMMLayout -> CBool -> IO ()

foreign import ccall interruptible
               "OGDFFMMMLayout.h FMMMLayout_fMMMLayout_unitEdgeLength"
               c_fmmmlayout_fmmmlayout_unitedgelength ::
               Ptr RawFMMMLayout -> CDouble -> IO ()

foreign import ccall interruptible
               "OGDFFMMMLayout.h FMMMLayout_fMMMLayout_newInitialPlacement"
               c_fmmmlayout_fmmmlayout_newinitialplacement ::
               Ptr RawFMMMLayout -> CBool -> IO ()