{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module OGDF.Graph.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.Graph.RawType import OGDF.Graph.FFI import OGDF.Graph.Interface import OGDF.Graph.Cast import OGDF.Graph.RawType import OGDF.Graph.Cast import OGDF.Graph.Interface import OGDF.NodeElement.RawType import OGDF.NodeElement.Cast import OGDF.NodeElement.Interface import OGDF.EdgeElement.RawType import OGDF.EdgeElement.Cast import OGDF.EdgeElement.Interface import STD.Deletable.RawType import STD.Deletable.Cast import STD.Deletable.Interface instance () => IGraph (Graph) where instance () => IDeletable (Graph) where delete = xform0 c_graph_delete newGraph :: () => IO Graph newGraph = xformnull c_graph_newgraph graph_newNode :: () => Graph -> IO NodeElement graph_newNode = xform0 c_graph_graph_newnode newNode1 :: () => Graph -> CInt -> IO NodeElement newNode1 = xform1 c_graph_newnode1 graph_newEdge :: (INodeElement c1, FPtr c1, INodeElement c0, FPtr c0) => Graph -> c0 -> c1 -> IO EdgeElement graph_newEdge = xform2 c_graph_graph_newedge graph_firstNode :: () => Graph -> IO NodeElement graph_firstNode = xform0 c_graph_graph_firstnode graph_lastNode :: () => Graph -> IO NodeElement graph_lastNode = xform0 c_graph_graph_lastnode graph_firstEdge :: () => Graph -> IO EdgeElement graph_firstEdge = xform0 c_graph_graph_firstedge graph_lastEdge :: () => Graph -> IO EdgeElement graph_lastEdge = xform0 c_graph_graph_lastedge