{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Class.TShape.Implementation where import HROOT.TypeCast import HROOT.Class.TShape.RawType import HROOT.Class.TShape.FFI import HROOT.Class.TShape.Interface import HROOT.Class.TShape.Cast import HROOT.Class.TClass.RawType import HROOT.Class.TClass.Cast import HROOT.Class.TClass.Interface import HROOT.Class.TNamed.RawType import HROOT.Class.TNamed.Cast import HROOT.Class.TNamed.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.TAtt3D.RawType import HROOT.Class.TAtt3D.Cast import HROOT.Class.TAtt3D.Interface import HROOT.Class.TObject.RawType import HROOT.Class.TObject.Cast import HROOT.Class.TObject.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 ITShape TShape where instance ITNamed TShape where setName = xform1 c_tshape_setname setNameTitle = xform2 c_tshape_setnametitle setTitle = xform1 c_tshape_settitle instance ITAttLine TShape where getLineColor = xform0 c_tshape_getlinecolor getLineStyle = xform0 c_tshape_getlinestyle getLineWidth = xform0 c_tshape_getlinewidth resetAttLine = xform1 c_tshape_resetattline setLineAttributes = xform0 c_tshape_setlineattributes setLineColor = xform1 c_tshape_setlinecolor setLineStyle = xform1 c_tshape_setlinestyle setLineWidth = xform1 c_tshape_setlinewidth instance ITAttFill TShape where setFillColor = xform1 c_tshape_setfillcolor setFillStyle = xform1 c_tshape_setfillstyle instance ITAtt3D TShape where instance ITObject TShape where draw = xform1 c_tshape_draw findObject = xform1 c_tshape_findobject getName = xform0 c_tshape_getname isA = xform0 c_tshape_isa isFolder = xform0 c_tshape_isfolder isEqual = xform1 c_tshape_isequal isSortable = xform0 c_tshape_issortable paint = xform1 c_tshape_paint printObj = xform1 c_tshape_printobj recursiveRemove = xform1 c_tshape_recursiveremove saveAs = xform2 c_tshape_saveas useCurrentStyle = xform0 c_tshape_usecurrentstyle write = xform3 c_tshape_write instance IDeletable TShape where delete = xform0 c_tshape_delete instance ITShape (Exist TShape) where instance ITNamed (Exist TShape) where setName (ETShape x) = setName x setNameTitle (ETShape x) = setNameTitle x setTitle (ETShape x) = setTitle x instance ITAttLine (Exist TShape) where getLineColor (ETShape x) = getLineColor x getLineStyle (ETShape x) = getLineStyle x getLineWidth (ETShape x) = getLineWidth x resetAttLine (ETShape x) = resetAttLine x setLineAttributes (ETShape x) = setLineAttributes x setLineColor (ETShape x) = setLineColor x setLineStyle (ETShape x) = setLineStyle x setLineWidth (ETShape x) = setLineWidth x instance ITAttFill (Exist TShape) where setFillColor (ETShape x) = setFillColor x setFillStyle (ETShape x) = setFillStyle x instance ITAtt3D (Exist TShape) where instance ITObject (Exist TShape) where draw (ETShape x) = draw x findObject (ETShape x) = findObject x getName (ETShape x) = getName x isA (ETShape x) = isA x isFolder (ETShape x) = isFolder x isEqual (ETShape x) = isEqual x isSortable (ETShape x) = isSortable x paint (ETShape x) = paint x printObj (ETShape x) = printObj x recursiveRemove (ETShape x) = recursiveRemove x saveAs (ETShape x) = saveAs x useCurrentStyle (ETShape x) = useCurrentStyle x write (ETShape x) = write x instance IDeletable (Exist TShape) where delete (ETShape x) = delete x newTShape :: String -> String -> String -> IO TShape newTShape = xform2 c_tshape_newtshape instance FPtr (Exist TShape) where type Raw (Exist TShape) = RawTShape get_fptr (ETShape obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETShape (cast_fptr_to_obj (fptr :: ForeignPtr RawTShape) :: TShape)