{-# LANGUAGE EmptyDataDecls, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, IncoherentInstances, MultiParamTypeClasses, OverlappingInstances, TemplateHaskell, TypeFamilies, TypeSynonymInstances #-} module HROOT.Hist.TAxis.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.Hist.TAxis.RawType import HROOT.Hist.TAxis.FFI import HROOT.Hist.TAxis.Interface import HROOT.Hist.TAxis.Cast import HROOT.Hist.TAxis.RawType import HROOT.Hist.TAxis.Cast import HROOT.Hist.TAxis.Interface import HROOT.Core.TClass.RawType import HROOT.Core.TClass.Cast import HROOT.Core.TClass.Interface import HROOT.Core.TArrayD.RawType import HROOT.Core.TArrayD.Cast import HROOT.Core.TArrayD.Interface import HROOT.Core.TNamed.RawType import HROOT.Core.TNamed.Cast import HROOT.Core.TNamed.Interface import HROOT.Core.TAttAxis.RawType import HROOT.Core.TAttAxis.Cast import HROOT.Core.TAttAxis.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 () => ITAxis (TAxis) where findBinTAxis = xform1 c_taxis_findbintaxis findFixBinTAxis = xform1 c_taxis_findfixbintaxis getBinCenterTAxis = xform1 c_taxis_getbincentertaxis getBinCenterLog = xform1 c_taxis_getbincenterlog getBinUpEdge = xform1 c_taxis_getbinupedge setLimits = xform2 c_taxis_setlimits setTimeDisplay = xform1 c_taxis_settimedisplay setTimeFormat = xform1 c_taxis_settimeformat setTimeOffset = xform2 c_taxis_settimeoffset instance () => ITNamed (TAxis) where setName = xform1 c_taxis_setname setNameTitle = xform2 c_taxis_setnametitle setTitle = xform1 c_taxis_settitle instance () => ITAttAxis (TAxis) where getNdivisions = xform0 c_taxis_getndivisions getAxisColor = xform0 c_taxis_getaxiscolor getLabelColor = xform0 c_taxis_getlabelcolor getLabelFont = xform0 c_taxis_getlabelfont getLabelOffset = xform0 c_taxis_getlabeloffset getLabelSize = xform0 c_taxis_getlabelsize getTitleOffset = xform0 c_taxis_gettitleoffset getTitleSize = xform0 c_taxis_gettitlesize getTickLength = xform0 c_taxis_getticklength getTitleFont = xform0 c_taxis_gettitlefont setNdivisions = xform2 c_taxis_setndivisions setAxisColor = xform1 c_taxis_setaxiscolor setLabelColor = xform1 c_taxis_setlabelcolor setLabelFont = xform1 c_taxis_setlabelfont setLabelOffset = xform1 c_taxis_setlabeloffset setLabelSize = xform1 c_taxis_setlabelsize setTickLength = xform1 c_taxis_setticklength setTitleOffset = xform1 c_taxis_settitleoffset setTitleSize = xform1 c_taxis_settitlesize setTitleColor = xform1 c_taxis_settitlecolor setTitleFont = xform1 c_taxis_settitlefont instance () => ITObject (TAxis) where clear = xform1 c_taxis_clear draw = xform1 c_taxis_draw findObject = xform1 c_taxis_findobject getName = xform0 c_taxis_getname isA = xform0 c_taxis_isa paint = xform1 c_taxis_paint printObj = xform1 c_taxis_printobj saveAs = xform2 c_taxis_saveas write = xform3 c_taxis_write write_ = xform0 c_taxis_write_ instance () => IDeletable (TAxis) where delete = xform0 c_taxis_delete newTAxis :: () => CInt -> CDouble -> CDouble -> IO TAxis newTAxis = xform2 c_taxis_newtaxis tAxis_GetCenterLabels :: () => TAxis -> IO CBool tAxis_GetCenterLabels = xform0 c_taxis_taxis_getcenterlabels tAxis_GetCenterTitle :: () => TAxis -> IO CBool tAxis_GetCenterTitle = xform0 c_taxis_taxis_getcentertitle tAxis_GetFirst :: () => TAxis -> IO CInt tAxis_GetFirst = xform0 c_taxis_taxis_getfirst tAxis_GetLast :: () => TAxis -> IO CInt tAxis_GetLast = xform0 c_taxis_taxis_getlast tAxis_GetNbins :: () => TAxis -> IO CInt tAxis_GetNbins = xform0 c_taxis_taxis_getnbins tAxis_GetXbins :: () => TAxis -> IO TArrayD tAxis_GetXbins = xform0 c_taxis_taxis_getxbins tAxis_GetXmax :: () => TAxis -> IO CDouble tAxis_GetXmax = xform0 c_taxis_taxis_getxmax tAxis_GetXmin :: () => TAxis -> IO CDouble tAxis_GetXmin = xform0 c_taxis_taxis_getxmin