{-# 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 = xform0 c_graphattributes_boundingbox instance () => IDeletable (GraphAttributes) where delete = xform0 c_graphattributes_delete newGraphAttributes :: (IGraph c0, FPtr c0) => c0 -> CLong -> IO GraphAttributes newGraphAttributes = xform1 c_graphattributes_newgraphattributes graphAttributes_fillColor :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO Color graphAttributes_fillColor = xform1 c_graphattributes_graphattributes_fillcolor graphAttributes_fillBgColor :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO Color graphAttributes_fillBgColor = xform1 c_graphattributes_graphattributes_fillbgcolor graphAttributes_x :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_x = xform1 c_graphattributes_graphattributes_x graphAttributes_y :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_y = xform1 c_graphattributes_graphattributes_y graphAttributes_width :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_width = xform1 c_graphattributes_graphattributes_width graphAttributes_height :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_height = xform1 c_graphattributes_graphattributes_height graphAttributes_bends :: (IEdgeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (List DPoint) graphAttributes_bends = xform1 c_graphattributes_graphattributes_bends graphAttributes_label :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO CppString graphAttributes_label = xform1 c_graphattributes_graphattributes_label graphAttributeslabelE :: (IEdgeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO CppString graphAttributeslabelE = xform1 c_graphattributes_graphattributeslabele graphAttributes_xLabel :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_xLabel = xform1 c_graphattributes_graphattributes_xlabel graphAttributes_yLabel :: (INodeElement c0, FPtr c0) => GraphAttributes -> c0 -> IO (Ptr CDouble) graphAttributes_yLabel = xform1 c_graphattributes_graphattributes_ylabel