{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Class.TChain.Implementation where import HROOT.TypeCast import HROOT.Class.TChain.RawType import HROOT.Class.TChain.FFI import HROOT.Class.TChain.Interface import HROOT.Class.TChain.Cast import HROOT.Class.TClass.RawType import HROOT.Class.TClass.Cast import HROOT.Class.TClass.Interface import HROOT.Class.TTree.RawType import HROOT.Class.TTree.Cast import HROOT.Class.TTree.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.TAttMarker.RawType import HROOT.Class.TAttMarker.Cast import HROOT.Class.TAttMarker.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 ITChain TChain where instance ITTree TChain where instance ITNamed TChain where setName = xform1 c_tchain_setname setNameTitle = xform2 c_tchain_setnametitle setTitle = xform1 c_tchain_settitle instance ITAttLine TChain where getLineColor = xform0 c_tchain_getlinecolor getLineStyle = xform0 c_tchain_getlinestyle getLineWidth = xform0 c_tchain_getlinewidth resetAttLine = xform1 c_tchain_resetattline setLineAttributes = xform0 c_tchain_setlineattributes setLineColor = xform1 c_tchain_setlinecolor setLineStyle = xform1 c_tchain_setlinestyle setLineWidth = xform1 c_tchain_setlinewidth instance ITAttFill TChain where setFillColor = xform1 c_tchain_setfillcolor setFillStyle = xform1 c_tchain_setfillstyle instance ITAttMarker TChain where getMarkerColor = xform0 c_tchain_getmarkercolor getMarkerStyle = xform0 c_tchain_getmarkerstyle getMarkerSize = xform0 c_tchain_getmarkersize resetAttMarker = xform1 c_tchain_resetattmarker setMarkerAttributes = xform0 c_tchain_setmarkerattributes setMarkerColor = xform1 c_tchain_setmarkercolor setMarkerStyle = xform1 c_tchain_setmarkerstyle setMarkerSize = xform1 c_tchain_setmarkersize instance ITObject TChain where draw = xform1 c_tchain_draw findObject = xform1 c_tchain_findobject getName = xform0 c_tchain_getname isA = xform0 c_tchain_isa isFolder = xform0 c_tchain_isfolder isEqual = xform1 c_tchain_isequal isSortable = xform0 c_tchain_issortable paint = xform1 c_tchain_paint printObj = xform1 c_tchain_printobj recursiveRemove = xform1 c_tchain_recursiveremove saveAs = xform2 c_tchain_saveas useCurrentStyle = xform0 c_tchain_usecurrentstyle write = xform3 c_tchain_write instance IDeletable TChain where delete = xform0 c_tchain_delete instance ITChain (Exist TChain) where instance ITTree (Exist TChain) where instance ITNamed (Exist TChain) where setName (ETChain x) = setName x setNameTitle (ETChain x) = setNameTitle x setTitle (ETChain x) = setTitle x instance ITAttLine (Exist TChain) where getLineColor (ETChain x) = getLineColor x getLineStyle (ETChain x) = getLineStyle x getLineWidth (ETChain x) = getLineWidth x resetAttLine (ETChain x) = resetAttLine x setLineAttributes (ETChain x) = setLineAttributes x setLineColor (ETChain x) = setLineColor x setLineStyle (ETChain x) = setLineStyle x setLineWidth (ETChain x) = setLineWidth x instance ITAttFill (Exist TChain) where setFillColor (ETChain x) = setFillColor x setFillStyle (ETChain x) = setFillStyle x instance ITAttMarker (Exist TChain) where getMarkerColor (ETChain x) = getMarkerColor x getMarkerStyle (ETChain x) = getMarkerStyle x getMarkerSize (ETChain x) = getMarkerSize x resetAttMarker (ETChain x) = resetAttMarker x setMarkerAttributes (ETChain x) = setMarkerAttributes x setMarkerColor (ETChain x) = setMarkerColor x setMarkerStyle (ETChain x) = setMarkerStyle x setMarkerSize (ETChain x) = setMarkerSize x instance ITObject (Exist TChain) where draw (ETChain x) = draw x findObject (ETChain x) = findObject x getName (ETChain x) = getName x isA (ETChain x) = isA x isFolder (ETChain x) = isFolder x isEqual (ETChain x) = isEqual x isSortable (ETChain x) = isSortable x paint (ETChain x) = paint x printObj (ETChain x) = printObj x recursiveRemove (ETChain x) = recursiveRemove x saveAs (ETChain x) = saveAs x useCurrentStyle (ETChain x) = useCurrentStyle x write (ETChain x) = write x instance IDeletable (Exist TChain) where delete (ETChain x) = delete x newTChain :: String -> String -> IO TChain newTChain = xform1 c_tchain_newtchain instance FPtr (Exist TChain) where type Raw (Exist TChain) = RawTChain get_fptr (ETChain obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETChain (cast_fptr_to_obj (fptr :: ForeignPtr RawTChain) :: TChain)