{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module HROOT.Core.TStyle.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 HROOT.Core.TStyle.RawType import HROOT.Core.TStyle.FFI import HROOT.Core.TStyle.Interface import HROOT.Core.TStyle.Cast import HROOT.Core.TStyle.RawType import HROOT.Core.TStyle.Cast import HROOT.Core.TStyle.Interface import HROOT.Core.TClass.RawType import HROOT.Core.TClass.Cast import HROOT.Core.TClass.Interface import HROOT.Core.TNamed.RawType import HROOT.Core.TNamed.Cast import HROOT.Core.TNamed.Interface import HROOT.Core.TAttLine.RawType import HROOT.Core.TAttLine.Cast import HROOT.Core.TAttLine.Interface import HROOT.Core.TAttFill.RawType import HROOT.Core.TAttFill.Cast import HROOT.Core.TAttFill.Interface import HROOT.Core.TAttMarker.RawType import HROOT.Core.TAttMarker.Cast import HROOT.Core.TAttMarker.Interface import HROOT.Core.TAttText.RawType import HROOT.Core.TAttText.Cast import HROOT.Core.TAttText.Interface import HROOT.Core.TObject.RawType import HROOT.Core.TObject.Cast import HROOT.Core.TObject.Interface import STD.Deletable.RawType import STD.Deletable.Cast import STD.Deletable.Interface instance () => ITStyle (TStyle) where instance () => ITNamed (TStyle) where setName = xform1 c_tstyle_setname setNameTitle = xform2 c_tstyle_setnametitle setTitle = xform1 c_tstyle_settitle instance () => ITAttLine (TStyle) where getLineColor = xform0 c_tstyle_getlinecolor getLineStyle = xform0 c_tstyle_getlinestyle getLineWidth = xform0 c_tstyle_getlinewidth resetAttLine = xform1 c_tstyle_resetattline setLineAttributes = xform0 c_tstyle_setlineattributes setLineColor = xform1 c_tstyle_setlinecolor setLineStyle = xform1 c_tstyle_setlinestyle setLineWidth = xform1 c_tstyle_setlinewidth instance () => ITAttFill (TStyle) where setFillColor = xform1 c_tstyle_setfillcolor setFillStyle = xform1 c_tstyle_setfillstyle instance () => ITAttMarker (TStyle) where getMarkerColor = xform0 c_tstyle_getmarkercolor getMarkerStyle = xform0 c_tstyle_getmarkerstyle getMarkerSize = xform0 c_tstyle_getmarkersize resetAttMarker = xform1 c_tstyle_resetattmarker setMarkerAttributes = xform0 c_tstyle_setmarkerattributes setMarkerColor = xform1 c_tstyle_setmarkercolor setMarkerStyle = xform1 c_tstyle_setmarkerstyle setMarkerSize = xform1 c_tstyle_setmarkersize instance () => ITAttText (TStyle) where getTextAlign = xform0 c_tstyle_gettextalign getTextAngle = xform0 c_tstyle_gettextangle getTextColor = xform0 c_tstyle_gettextcolor getTextFont = xform0 c_tstyle_gettextfont getTextSize = xform0 c_tstyle_gettextsize resetAttText = xform1 c_tstyle_resetatttext setTextAttributes = xform0 c_tstyle_settextattributes setTextAlign = xform1 c_tstyle_settextalign setTextAngle = xform1 c_tstyle_settextangle setTextColor = xform1 c_tstyle_settextcolor setTextFont = xform1 c_tstyle_settextfont setTextSize = xform1 c_tstyle_settextsize setTextSizePixels = xform1 c_tstyle_settextsizepixels instance () => ITObject (TStyle) where clear = xform1 c_tstyle_clear draw = xform1 c_tstyle_draw findObject = xform1 c_tstyle_findobject getName = xform0 c_tstyle_getname isA = xform0 c_tstyle_isa paint = xform1 c_tstyle_paint printObj = xform1 c_tstyle_printobj saveAs = xform2 c_tstyle_saveas write = xform3 c_tstyle_write write_ = xform0 c_tstyle_write_ instance () => IDeletable (TStyle) where delete = xform0 c_tstyle_delete tStyle_SetCanvasPreferGL :: () => TStyle -> CBool -> IO () tStyle_SetCanvasPreferGL = xform1 c_tstyle_tstyle_setcanvasprefergl tStyle_SetOptDate :: () => TStyle -> CInt -> IO () tStyle_SetOptDate = xform1 c_tstyle_tstyle_setoptdate tStyle_SetOptFile :: () => TStyle -> CInt -> IO () tStyle_SetOptFile = xform1 c_tstyle_tstyle_setoptfile tStyle_SetOptFit :: () => TStyle -> CInt -> IO () tStyle_SetOptFit = xform1 c_tstyle_tstyle_setoptfit tStyle_SetOptLogx :: () => TStyle -> CInt -> IO () tStyle_SetOptLogx = xform1 c_tstyle_tstyle_setoptlogx tStyle_SetOptLogy :: () => TStyle -> CInt -> IO () tStyle_SetOptLogy = xform1 c_tstyle_tstyle_setoptlogy tStyle_SetOptLogz :: () => TStyle -> CInt -> IO () tStyle_SetOptLogz = xform1 c_tstyle_tstyle_setoptlogz tStyle_SetOptStat :: () => TStyle -> CInt -> IO () tStyle_SetOptStat = xform1 c_tstyle_tstyle_setoptstat tStyle_SetOptTitle :: () => TStyle -> CInt -> IO () tStyle_SetOptTitle = xform1 c_tstyle_tstyle_setopttitle tStyle_SetPalette :: () => TStyle -> CInt -> IO () tStyle_SetPalette = xform1 c_tstyle_tstyle_setpalette