{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, 
             FlexibleInstances, TypeSynonymInstances, EmptyDataDecls, 
             OverlappingInstances, IncoherentInstances #-}

module HROOT.Hist.TGraphErrors.Implementation where


import FFICXX.Runtime.Cast

import HROOT.Hist.TGraphErrors.RawType
import HROOT.Hist.TGraphErrors.FFI
import HROOT.Hist.TGraphErrors.Interface
import HROOT.Hist.TGraphErrors.Cast
import HROOT.Hist.TF1.RawType
import HROOT.Hist.TF1.Cast
import HROOT.Hist.TF1.Interface
import HROOT.Hist.TH1F.RawType
import HROOT.Hist.TH1F.Cast
import HROOT.Hist.TH1F.Interface
import HROOT.Hist.TAxis.RawType
import HROOT.Hist.TAxis.Cast
import HROOT.Hist.TAxis.Interface
import HROOT.Core.TClass.RawType
import HROOT.Core.TClass.Cast
import HROOT.Core.TClass.Interface
import HROOT.Hist.TGraph.RawType
import HROOT.Hist.TGraph.Cast
import HROOT.Hist.TGraph.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.TAttMarker.RawType
import HROOT.Core.TAttMarker.Cast
import HROOT.Core.TAttMarker.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 ITGraphErrors TGraphErrors where
instance ITGraph TGraphErrors where
  apply = xform1 c_tgrapherrors_apply
  chisquare = xform1 c_tgrapherrors_chisquare
  drawGraph = xform4 c_tgrapherrors_drawgraph
  drawPanelTGraph = xform0 c_tgrapherrors_drawpaneltgraph
  expand = xform2 c_tgrapherrors_expand
  fitPanelTGraph = xform0 c_tgrapherrors_fitpaneltgraph
  getCorrelationFactorTGraph = xform0 c_tgrapherrors_getcorrelationfactortgraph
  getCovarianceTGraph = xform0 c_tgrapherrors_getcovariancetgraph
  getMeanTGraph = xform1 c_tgrapherrors_getmeantgraph
  getRMSTGraph = xform1 c_tgrapherrors_getrmstgraph
  getErrorX = xform1 c_tgrapherrors_geterrorx
  getErrorY = xform1 c_tgrapherrors_geterrory
  getErrorXhigh = xform1 c_tgrapherrors_geterrorxhigh
  getErrorXlow = xform1 c_tgrapherrors_geterrorxlow
  getErrorYhigh = xform1 c_tgrapherrors_geterroryhigh
  getErrorYlow = xform1 c_tgrapherrors_geterrorylow
  initExpo = xform2 c_tgrapherrors_initexpo
  initGaus = xform2 c_tgrapherrors_initgaus
  initPolynom = xform2 c_tgrapherrors_initpolynom
  insertPoint = xform0 c_tgrapherrors_insertpoint
  integralTGraph = xform2 c_tgrapherrors_integraltgraph
  isEditable = xform0 c_tgrapherrors_iseditable
  isInsideTGraph = xform2 c_tgrapherrors_isinsidetgraph
  leastSquareFit = xform4 c_tgrapherrors_leastsquarefit
  paintStats = xform1 c_tgrapherrors_paintstats
  removePoint = xform1 c_tgrapherrors_removepoint
  setEditable = xform1 c_tgrapherrors_seteditable
  setHistogram = xform1 c_tgrapherrors_sethistogram
  setMaximumTGraph = xform1 c_tgrapherrors_setmaximumtgraph
  setMinimumTGraph = xform1 c_tgrapherrors_setminimumtgraph
  set = xform1 c_tgrapherrors_set
  setPoint = xform3 c_tgrapherrors_setpoint
instance ITNamed TGraphErrors where
  setName = xform1 c_tgrapherrors_setname
  setNameTitle = xform2 c_tgrapherrors_setnametitle
  setTitle = xform1 c_tgrapherrors_settitle
instance ITAttLine TGraphErrors where
  getLineColor = xform0 c_tgrapherrors_getlinecolor
  getLineStyle = xform0 c_tgrapherrors_getlinestyle
  getLineWidth = xform0 c_tgrapherrors_getlinewidth
  resetAttLine = xform1 c_tgrapherrors_resetattline
  setLineAttributes = xform0 c_tgrapherrors_setlineattributes
  setLineColor = xform1 c_tgrapherrors_setlinecolor
  setLineStyle = xform1 c_tgrapherrors_setlinestyle
  setLineWidth = xform1 c_tgrapherrors_setlinewidth
instance ITAttFill TGraphErrors where
  setFillColor = xform1 c_tgrapherrors_setfillcolor
  setFillStyle = xform1 c_tgrapherrors_setfillstyle
instance ITAttMarker TGraphErrors where
  getMarkerColor = xform0 c_tgrapherrors_getmarkercolor
  getMarkerStyle = xform0 c_tgrapherrors_getmarkerstyle
  getMarkerSize = xform0 c_tgrapherrors_getmarkersize
  resetAttMarker = xform1 c_tgrapherrors_resetattmarker
  setMarkerAttributes = xform0 c_tgrapherrors_setmarkerattributes
  setMarkerColor = xform1 c_tgrapherrors_setmarkercolor
  setMarkerStyle = xform1 c_tgrapherrors_setmarkerstyle
  setMarkerSize = xform1 c_tgrapherrors_setmarkersize
instance ITObject TGraphErrors where
  draw = xform1 c_tgrapherrors_draw
  findObject = xform1 c_tgrapherrors_findobject
  getName = xform0 c_tgrapherrors_getname
  isA = xform0 c_tgrapherrors_isa
  paint = xform1 c_tgrapherrors_paint
  printObj = xform1 c_tgrapherrors_printobj
  saveAs = xform2 c_tgrapherrors_saveas
  write = xform3 c_tgrapherrors_write
instance IDeletable TGraphErrors where
  delete = xform0 c_tgrapherrors_delete

instance ITGraphErrors (Exist TGraphErrors) where

instance ITGraph (Exist TGraphErrors) where
  apply (ETGraphErrors x) = apply x
  chisquare (ETGraphErrors x) = chisquare x
  drawGraph (ETGraphErrors x) = drawGraph x
  drawPanelTGraph (ETGraphErrors x) = drawPanelTGraph x
  expand (ETGraphErrors x) = expand x
  fitPanelTGraph (ETGraphErrors x) = fitPanelTGraph x
  getCorrelationFactorTGraph (ETGraphErrors x) = getCorrelationFactorTGraph x
  getCovarianceTGraph (ETGraphErrors x) = getCovarianceTGraph x
  getMeanTGraph (ETGraphErrors x) = getMeanTGraph x
  getRMSTGraph (ETGraphErrors x) = getRMSTGraph x
  getErrorX (ETGraphErrors x) = getErrorX x
  getErrorY (ETGraphErrors x) = getErrorY x
  getErrorXhigh (ETGraphErrors x) = getErrorXhigh x
  getErrorXlow (ETGraphErrors x) = getErrorXlow x
  getErrorYhigh (ETGraphErrors x) = getErrorYhigh x
  getErrorYlow (ETGraphErrors x) = getErrorYlow x
  initExpo (ETGraphErrors x) = initExpo x
  initGaus (ETGraphErrors x) = initGaus x
  initPolynom (ETGraphErrors x) = initPolynom x
  insertPoint (ETGraphErrors x) = insertPoint x
  integralTGraph (ETGraphErrors x) = integralTGraph x
  isEditable (ETGraphErrors x) = isEditable x
  isInsideTGraph (ETGraphErrors x) = isInsideTGraph x
  leastSquareFit (ETGraphErrors x) = leastSquareFit x
  paintStats (ETGraphErrors x) = paintStats x
  removePoint (ETGraphErrors x) = removePoint x
  setEditable (ETGraphErrors x) = setEditable x
  setHistogram (ETGraphErrors x) = setHistogram x
  setMaximumTGraph (ETGraphErrors x) = setMaximumTGraph x
  setMinimumTGraph (ETGraphErrors x) = setMinimumTGraph x
  set (ETGraphErrors x) = set x
  setPoint (ETGraphErrors x) = setPoint x
instance ITNamed (Exist TGraphErrors) where
  setName (ETGraphErrors x) = setName x
  setNameTitle (ETGraphErrors x) = setNameTitle x
  setTitle (ETGraphErrors x) = setTitle x
instance ITAttLine (Exist TGraphErrors) where
  getLineColor (ETGraphErrors x) = getLineColor x
  getLineStyle (ETGraphErrors x) = getLineStyle x
  getLineWidth (ETGraphErrors x) = getLineWidth x
  resetAttLine (ETGraphErrors x) = resetAttLine x
  setLineAttributes (ETGraphErrors x) = setLineAttributes x
  setLineColor (ETGraphErrors x) = setLineColor x
  setLineStyle (ETGraphErrors x) = setLineStyle x
  setLineWidth (ETGraphErrors x) = setLineWidth x
instance ITAttFill (Exist TGraphErrors) where
  setFillColor (ETGraphErrors x) = setFillColor x
  setFillStyle (ETGraphErrors x) = setFillStyle x
instance ITAttMarker (Exist TGraphErrors) where
  getMarkerColor (ETGraphErrors x) = getMarkerColor x
  getMarkerStyle (ETGraphErrors x) = getMarkerStyle x
  getMarkerSize (ETGraphErrors x) = getMarkerSize x
  resetAttMarker (ETGraphErrors x) = resetAttMarker x
  setMarkerAttributes (ETGraphErrors x) = setMarkerAttributes x
  setMarkerColor (ETGraphErrors x) = setMarkerColor x
  setMarkerStyle (ETGraphErrors x) = setMarkerStyle x
  setMarkerSize (ETGraphErrors x) = setMarkerSize x
instance ITObject (Exist TGraphErrors) where
  draw (ETGraphErrors x) = draw x
  findObject (ETGraphErrors x) = findObject x
  getName (ETGraphErrors x) = getName x
  isA (ETGraphErrors x) = isA x
  paint (ETGraphErrors x) = paint x
  printObj (ETGraphErrors x) = printObj x
  saveAs (ETGraphErrors x) = saveAs x
  write (ETGraphErrors x) = write x
instance IDeletable (Exist TGraphErrors) where
  delete (ETGraphErrors x) = delete x


newTGraphErrors :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> IO TGraphErrors
newTGraphErrors = xform4 c_tgrapherrors_newtgrapherrors





instance FPtr (Exist TGraphErrors) where
  type Raw (Exist TGraphErrors) = RawTGraphErrors
  get_fptr (ETGraphErrors obj) = castForeignPtr (get_fptr obj)
  cast_fptr_to_obj fptr = ETGraphErrors (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraphErrors) :: TGraphErrors)