{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, OverlappingInstances, IncoherentInstances #-} module HROOT.Class.TCrown.Implementation where import HROOT.TypeCast import HROOT.Class.TCrown.RawType import HROOT.Class.TCrown.FFI import HROOT.Class.TCrown.Interface import HROOT.Class.TCrown.Cast import HROOT.Class.TClass.RawType import HROOT.Class.TClass.Cast import HROOT.Class.TClass.Interface import HROOT.Class.TEllipse.RawType import HROOT.Class.TEllipse.Cast import HROOT.Class.TEllipse.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 ITCrown TCrown where instance ITEllipse TCrown where instance ITObject TCrown where draw = xform1 c_tcrown_draw findObject = xform1 c_tcrown_findobject getName = xform0 c_tcrown_getname isA = xform0 c_tcrown_isa isFolder = xform0 c_tcrown_isfolder isEqual = xform1 c_tcrown_isequal isSortable = xform0 c_tcrown_issortable paint = xform1 c_tcrown_paint printObj = xform1 c_tcrown_printobj recursiveRemove = xform1 c_tcrown_recursiveremove saveAs = xform2 c_tcrown_saveas useCurrentStyle = xform0 c_tcrown_usecurrentstyle write = xform3 c_tcrown_write instance ITAttLine TCrown where getLineColor = xform0 c_tcrown_getlinecolor getLineStyle = xform0 c_tcrown_getlinestyle getLineWidth = xform0 c_tcrown_getlinewidth resetAttLine = xform1 c_tcrown_resetattline setLineAttributes = xform0 c_tcrown_setlineattributes setLineColor = xform1 c_tcrown_setlinecolor setLineStyle = xform1 c_tcrown_setlinestyle setLineWidth = xform1 c_tcrown_setlinewidth instance ITAttFill TCrown where setFillColor = xform1 c_tcrown_setfillcolor setFillStyle = xform1 c_tcrown_setfillstyle instance IDeletable TCrown where delete = xform0 c_tcrown_delete instance ITCrown (Exist TCrown) where instance ITEllipse (Exist TCrown) where instance ITObject (Exist TCrown) where draw (ETCrown x) = draw x findObject (ETCrown x) = findObject x getName (ETCrown x) = getName x isA (ETCrown x) = isA x isFolder (ETCrown x) = isFolder x isEqual (ETCrown x) = isEqual x isSortable (ETCrown x) = isSortable x paint (ETCrown x) = paint x printObj (ETCrown x) = printObj x recursiveRemove (ETCrown x) = recursiveRemove x saveAs (ETCrown x) = saveAs x useCurrentStyle (ETCrown x) = useCurrentStyle x write (ETCrown x) = write x instance ITAttLine (Exist TCrown) where getLineColor (ETCrown x) = getLineColor x getLineStyle (ETCrown x) = getLineStyle x getLineWidth (ETCrown x) = getLineWidth x resetAttLine (ETCrown x) = resetAttLine x setLineAttributes (ETCrown x) = setLineAttributes x setLineColor (ETCrown x) = setLineColor x setLineStyle (ETCrown x) = setLineStyle x setLineWidth (ETCrown x) = setLineWidth x instance ITAttFill (Exist TCrown) where setFillColor (ETCrown x) = setFillColor x setFillStyle (ETCrown x) = setFillStyle x instance IDeletable (Exist TCrown) where delete (ETCrown x) = delete x newTCrown :: Double -> Double -> Double -> Double -> Double -> Double -> IO TCrown newTCrown = xform5 c_tcrown_newtcrown instance FPtr (Exist TCrown) where type Raw (Exist TCrown) = RawTCrown get_fptr (ETCrown obj) = castForeignPtr (get_fptr obj) cast_fptr_to_obj fptr = ETCrown (cast_fptr_to_obj (fptr :: ForeignPtr RawTCrown) :: TCrown)