{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module OGDF.GraphAttributes.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.GraphAttributes.RawType import OGDF.GraphAttributes.FFI import OGDF.GraphAttributes.Interface import OGDF.GraphAttributes.Cast import OGDF.GraphAttributes.RawType import OGDF.GraphAttributes.Cast import OGDF.GraphAttributes.Interface import OGDF.Color.RawType import OGDF.Color.Cast import OGDF.Color.Interface import OGDF.List.Template import OGDF.DPoint.RawType import OGDF.DPoint.Cast import OGDF.DPoint.Interface import STD.CppString.RawType import STD.CppString.Cast import STD.CppString.Interface import OGDF.DRect.RawType import OGDF.DRect.Cast import OGDF.DRect.Interface 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 () => IGraphAttributes (GraphAttributes) where boundingBox :: GraphAttributes -> IO DRect boundingBox = (Ptr RawGraphAttributes -> IO (Ptr RawDRect)) -> GraphAttributes -> IO DRect forall a ca y cy. (Castable a ca, Castable y cy) => (ca -> IO cy) -> a -> IO y xform0 Ptr RawGraphAttributes -> IO (Ptr RawDRect) c_graphattributes_boundingbox instance () => IDeletable (GraphAttributes) where delete :: GraphAttributes -> IO () delete = (Ptr RawGraphAttributes -> IO ()) -> GraphAttributes -> IO () forall a ca y cy. (Castable a ca, Castable y cy) => (ca -> IO cy) -> a -> IO y xform0 Ptr RawGraphAttributes -> IO () c_graphattributes_delete newGraphAttributes :: (IGraph c0, FPtr c0) => c0 -> CLong -> IO GraphAttributes newGraphAttributes :: forall c0. (IGraph c0, FPtr c0) => c0 -> CLong -> IO GraphAttributes newGraphAttributes = (Ptr RawGraph -> CLong -> IO (Ptr RawGraphAttributes)) -> c0 -> CLong -> IO GraphAttributes forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraph -> CLong -> IO (Ptr RawGraphAttributes) c_graphattributes_newgraphattributes graphAttributes_fillColor :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO Color graphAttributes_fillColor :: forall c0. (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO Color graphAttributes_fillColor = (Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr RawColor)) -> GraphAttributes -> c0 -> IO Color forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr RawColor) c_graphattributes_graphattributes_fillcolor graphAttributes_fillBgColor :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO Color graphAttributes_fillBgColor :: forall c0. (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO Color graphAttributes_fillBgColor = (Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr RawColor)) -> GraphAttributes -> c0 -> IO Color forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr RawColor) c_graphattributes_graphattributes_fillbgcolor graphAttributes_x :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_x :: forall c0. (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_x = (Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble)) -> GraphAttributes -> c0 -> IO (Ptr CDouble) forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble) c_graphattributes_graphattributes_x graphAttributes_y :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_y :: forall c0. (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_y = (Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble)) -> GraphAttributes -> c0 -> IO (Ptr CDouble) forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble) c_graphattributes_graphattributes_y graphAttributes_width :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_width :: forall c0. (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_width = (Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble)) -> GraphAttributes -> c0 -> IO (Ptr CDouble) forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble) c_graphattributes_graphattributes_width graphAttributes_height :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_height :: forall c0. (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_height = (Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble)) -> GraphAttributes -> c0 -> IO (Ptr CDouble) forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble) c_graphattributes_graphattributes_height graphAttributes_bends :: (IEdgeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (List DPoint) graphAttributes_bends :: forall c0. (IEdgeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (List DPoint) graphAttributes_bends = (Ptr RawGraphAttributes -> Ptr RawEdgeElement -> IO (Ptr (RawList DPoint))) -> GraphAttributes -> c0 -> IO (List DPoint) forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawEdgeElement -> IO (Ptr (RawList DPoint)) c_graphattributes_graphattributes_bends graphAttributes_label :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO CppString graphAttributes_label :: forall c0. (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO CppString graphAttributes_label = (Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr RawCppString)) -> GraphAttributes -> c0 -> IO CppString forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr RawCppString) c_graphattributes_graphattributes_label graphAttributeslabelE :: (IEdgeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO CppString graphAttributeslabelE :: forall c0. (IEdgeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO CppString graphAttributeslabelE = (Ptr RawGraphAttributes -> Ptr RawEdgeElement -> IO (Ptr RawCppString)) -> GraphAttributes -> c0 -> IO CppString forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawEdgeElement -> IO (Ptr RawCppString) c_graphattributes_graphattributeslabele graphAttributes_xLabel :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_xLabel :: forall c0. (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_xLabel = (Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble)) -> GraphAttributes -> c0 -> IO (Ptr CDouble) forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble) c_graphattributes_graphattributes_xlabel graphAttributes_yLabel :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_yLabel :: forall c0. (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_yLabel = (Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble)) -> GraphAttributes -> c0 -> IO (Ptr CDouble) forall a ca x1 cx1 y cy. (Castable a ca, Castable x1 cx1, Castable y cy) => (ca -> cx1 -> IO cy) -> a -> x1 -> IO y xform1 Ptr RawGraphAttributes -> Ptr RawNodeElement -> IO (Ptr CDouble) c_graphattributes_graphattributes_ylabel