{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Class.TLegend.Implementation where import HROOT.TypeCast import HROOT.Class.TLegend.RawType import HROOT.Class.TLegend.FFI import HROOT.Class.TLegend.Interface import HROOT.Class.TLegend.Cast import HROOT.Class.TClass.RawType import HROOT.Class.TClass.Cast import HROOT.Class.TClass.Interface import HROOT.Class.TLegendEntry.RawType import HROOT.Class.TLegendEntry.Cast import HROOT.Class.TLegendEntry.Interface import HROOT.Class.TPave.RawType import HROOT.Class.TPave.Cast import HROOT.Class.TPave.Interface import HROOT.Class.TAttText.RawType import HROOT.Class.TAttText.Cast import HROOT.Class.TAttText.Interface import HROOT.Class.TBox.RawType import HROOT.Class.TBox.Cast import HROOT.Class.TBox.Interface import HROOT.Class.TObject.RawType import HROOT.Class.TObject.Cast import HROOT.Class.TObject.Interface import HROOT.Class.TAttLine.RawType import HROOT.Class.TAttLine.Cast import HROOT.Class.TAttLine.Interface import HROOT.Class.TAttFill.RawType import HROOT.Class.TAttFill.Cast import HROOT.Class.TAttFill.Interface import HROOT.Class.Deletable.RawType import HROOT.Class.Deletable.Cast import HROOT.Class.Deletable.Interface import Data.Word -- import Foreign.C -- import Foreign.Ptr import Foreign.ForeignPtr import System.IO.Unsafe instance ITLegend TLegend where addEntry = xform3 c_tlegend_addentry instance ITPave TLegend where instance ITAttText TLegend where getTextAlign = xform0 c_tlegend_gettextalign getTextAngle = xform0 c_tlegend_gettextangle getTextColor = xform0 c_tlegend_gettextcolor getTextFont = xform0 c_tlegend_gettextfont getTextSize = xform0 c_tlegend_gettextsize resetAttText = xform1 c_tlegend_resetatttext setTextAttributes = xform0 c_tlegend_settextattributes setTextAlign = xform1 c_tlegend_settextalign setTextAngle = xform1 c_tlegend_settextangle setTextColor = xform1 c_tlegend_settextcolor setTextFont = xform1 c_tlegend_settextfont setTextSize = xform1 c_tlegend_settextsize setTextSizePixels = xform1 c_tlegend_settextsizepixels instance ITBox TLegend where instance ITObject TLegend where draw = xform1 c_tlegend_draw findObject = xform1 c_tlegend_findobject getName = xform0 c_tlegend_getname isA = xform0 c_tlegend_isa isFolder = xform0 c_tlegend_isfolder isEqual = xform1 c_tlegend_isequal isSortable = xform0 c_tlegend_issortable paint = xform1 c_tlegend_paint printObj = xform1 c_tlegend_printobj recursiveRemove = xform1 c_tlegend_recursiveremove saveAs = xform2 c_tlegend_saveas useCurrentStyle = xform0 c_tlegend_usecurrentstyle write = xform3 c_tlegend_write instance ITAttLine TLegend where getLineColor = xform0 c_tlegend_getlinecolor getLineStyle = xform0 c_tlegend_getlinestyle getLineWidth = xform0 c_tlegend_getlinewidth resetAttLine = xform1 c_tlegend_resetattline setLineAttributes = xform0 c_tlegend_setlineattributes setLineColor = xform1 c_tlegend_setlinecolor setLineStyle = xform1 c_tlegend_setlinestyle setLineWidth = xform1 c_tlegend_setlinewidth instance ITAttFill TLegend where setFillColor = xform1 c_tlegend_setfillcolor setFillStyle = xform1 c_tlegend_setfillstyle instance IDeletable TLegend where delete = xform0 c_tlegend_delete instance ITLegend (Exist TLegend) where addEntry (ETLegend x) = addEntry x instance ITPave (Exist TLegend) where instance ITAttText (Exist TLegend) where getTextAlign (ETLegend x) = getTextAlign x getTextAngle (ETLegend x) = getTextAngle x getTextColor (ETLegend x) = getTextColor x getTextFont (ETLegend x) = getTextFont x getTextSize (ETLegend x) = getTextSize x resetAttText (ETLegend x) = resetAttText x setTextAttributes (ETLegend x) = setTextAttributes x setTextAlign (ETLegend x) = setTextAlign x setTextAngle (ETLegend x) = setTextAngle x setTextColor (ETLegend x) = setTextColor x setTextFont (ETLegend x) = setTextFont x setTextSize (ETLegend x) = setTextSize x setTextSizePixels (ETLegend x) = setTextSizePixels x instance ITBox (Exist TLegend) where instance ITObject (Exist TLegend) where draw (ETLegend x) = draw x findObject (ETLegend x) = findObject x getName (ETLegend x) = getName x isA (ETLegend x) = isA x isFolder (ETLegend x) = isFolder x isEqual (ETLegend x) = isEqual x isSortable (ETLegend x) = isSortable x paint (ETLegend x) = paint x printObj (ETLegend x) = printObj x recursiveRemove (ETLegend x) = recursiveRemove x saveAs (ETLegend x) = saveAs x useCurrentStyle (ETLegend x) = useCurrentStyle x write (ETLegend x) = write x instance ITAttLine (Exist TLegend) where getLineColor (ETLegend x) = getLineColor x getLineStyle (ETLegend x) = getLineStyle x getLineWidth (ETLegend x) = getLineWidth x resetAttLine (ETLegend x) = resetAttLine x setLineAttributes (ETLegend x) = setLineAttributes x setLineColor (ETLegend x) = setLineColor x setLineStyle (ETLegend x) = setLineStyle x setLineWidth (ETLegend x) = setLineWidth x instance ITAttFill (Exist TLegend) where setFillColor (ETLegend x) = setFillColor x setFillStyle (ETLegend x) = setFillStyle x instance IDeletable (Exist TLegend) where delete (ETLegend x) = delete x newTLegend :: Double -> Double -> Double -> Double -> String -> String -> IO TLegend newTLegend = xform5 c_tlegend_newtlegend instance FPtr (Exist TLegend) where type Raw (Exist TLegend) = RawTLegend get_fptr (ETLegend obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETLegend (cast_fptr_to_obj (fptr :: ForeignPtr RawTLegend) :: TLegend)