{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Graf.TPCON.Implementation where import FFICXX.Runtime.Cast import HROOT.Graf.TPCON.RawType import HROOT.Graf.TPCON.FFI import HROOT.Graf.TPCON.Interface import HROOT.Graf.TPCON.Cast import HROOT.Core.TClass.RawType import HROOT.Core.TClass.Cast import HROOT.Core.TClass.Interface import HROOT.Graf.TShape.RawType import HROOT.Graf.TShape.Cast import HROOT.Graf.TShape.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.TAtt3D.RawType import HROOT.Core.TAtt3D.Cast import HROOT.Core.TAtt3D.Interface import HROOT.Core.TObject.RawType import HROOT.Core.TObject.Cast import HROOT.Core.TObject.Interface import HROOT.Core.Deletable.RawType import HROOT.Core.Deletable.Cast import HROOT.Core.Deletable.Interface import Data.Word import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import System.IO.Unsafe instance ITPCON TPCON where instance ITShape TPCON where instance ITNamed TPCON where setName = xform1 c_tpcon_setname setNameTitle = xform2 c_tpcon_setnametitle setTitle = xform1 c_tpcon_settitle instance ITAttLine TPCON where getLineColor = xform0 c_tpcon_getlinecolor getLineStyle = xform0 c_tpcon_getlinestyle getLineWidth = xform0 c_tpcon_getlinewidth resetAttLine = xform1 c_tpcon_resetattline setLineAttributes = xform0 c_tpcon_setlineattributes setLineColor = xform1 c_tpcon_setlinecolor setLineStyle = xform1 c_tpcon_setlinestyle setLineWidth = xform1 c_tpcon_setlinewidth instance ITAttFill TPCON where setFillColor = xform1 c_tpcon_setfillcolor setFillStyle = xform1 c_tpcon_setfillstyle instance ITAtt3D TPCON where instance ITObject TPCON where draw = xform1 c_tpcon_draw findObject = xform1 c_tpcon_findobject getName = xform0 c_tpcon_getname isA = xform0 c_tpcon_isa paint = xform1 c_tpcon_paint printObj = xform1 c_tpcon_printobj saveAs = xform2 c_tpcon_saveas write = xform3 c_tpcon_write instance IDeletable TPCON where delete = xform0 c_tpcon_delete instance ITPCON (Exist TPCON) where instance ITShape (Exist TPCON) where instance ITNamed (Exist TPCON) where setName (ETPCON x) = setName x setNameTitle (ETPCON x) = setNameTitle x setTitle (ETPCON x) = setTitle x instance ITAttLine (Exist TPCON) where getLineColor (ETPCON x) = getLineColor x getLineStyle (ETPCON x) = getLineStyle x getLineWidth (ETPCON x) = getLineWidth x resetAttLine (ETPCON x) = resetAttLine x setLineAttributes (ETPCON x) = setLineAttributes x setLineColor (ETPCON x) = setLineColor x setLineStyle (ETPCON x) = setLineStyle x setLineWidth (ETPCON x) = setLineWidth x instance ITAttFill (Exist TPCON) where setFillColor (ETPCON x) = setFillColor x setFillStyle (ETPCON x) = setFillStyle x instance ITAtt3D (Exist TPCON) where instance ITObject (Exist TPCON) where draw (ETPCON x) = draw x findObject (ETPCON x) = findObject x getName (ETPCON x) = getName x isA (ETPCON x) = isA x paint (ETPCON x) = paint x printObj (ETPCON x) = printObj x saveAs (ETPCON x) = saveAs x write (ETPCON x) = write x instance IDeletable (Exist TPCON) where delete (ETPCON x) = delete x newTPCON :: CString -> CString -> CString -> CDouble -> CDouble -> CInt -> IO TPCON newTPCON = xform5 c_tpcon_newtpcon instance FPtr (Exist TPCON) where type Raw (Exist TPCON) = RawTPCON get_fptr (ETPCON obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETPCON (cast_fptr_to_obj (fptr :: ForeignPtr RawTPCON) :: TPCON)