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

foreign import ccall interruptible "OGDFGraphIO.h GraphIO_delete"
               c_graphio_delete :: Ptr RawGraphIO -> IO ()

foreign import ccall interruptible
               "OGDFGraphIO.h GraphIO_graphIO_read" c_graphio_graphio_read ::
               Ptr RawGraphAttributes ->
                 Ptr RawGraph -> Ptr RawCppString -> IO CBool

foreign import ccall interruptible
               "OGDFGraphIO.h GraphIO_graphIO_write" c_graphio_graphio_write ::
               Ptr RawGraphAttributes -> Ptr RawCppString -> IO CBool

foreign import ccall interruptible
               "OGDFGraphIO.h GraphIO_graphIO_drawSVG" c_graphio_graphio_drawsvg
               :: Ptr RawGraphAttributes -> Ptr RawCppString -> IO CBool