{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module OGDF.GraphIO.Implementation where import Data.Monoid import Data.Word import Data.Int import Foreign.C import Foreign.Ptr import Language.Haskell.TH import Language.Haskell.TH.Syntax import System.IO.Unsafe import FFICXX.Runtime.Cast import FFICXX.Runtime.CodeGen.Cxx import FFICXX.Runtime.TH import OGDF.GraphIO.RawType import OGDF.GraphIO.FFI import OGDF.GraphIO.Interface import OGDF.GraphIO.Cast import OGDF.GraphIO.RawType import OGDF.GraphIO.Cast import OGDF.GraphIO.Interface import OGDF.GraphAttributes.RawType import OGDF.GraphAttributes.Cast import OGDF.GraphAttributes.Interface import OGDF.Graph.RawType import OGDF.Graph.Cast import OGDF.Graph.Interface import STD.CppString.RawType import STD.CppString.Cast import STD.CppString.Interface import STD.Deletable.RawType import STD.Deletable.Cast import STD.Deletable.Interface instance () => IGraphIO (GraphIO) where instance () => IDeletable (GraphIO) where delete = xform0 c_graphio_delete graphIO_read :: (ICppString c2, FPtr c2, IGraph c1, FPtr c1, IGraphAttributes c0, FPtr c0) => c0 -> c1 -> c2 -> IO CBool graphIO_read = xform2 c_graphio_graphio_read graphIO_write :: (ICppString c1, FPtr c1, IGraphAttributes c0, FPtr c0) => c0 -> c1 -> IO CBool graphIO_write = xform1 c_graphio_graphio_write graphIO_drawSVG :: (ICppString c1, FPtr c1, IGraphAttributes c0, FPtr c0) => c0 -> c1 -> IO CBool graphIO_drawSVG = xform1 c_graphio_graphio_drawsvg