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

module HROOT.Hist.TGraph.Implementation where


import FFICXX.Runtime.Cast

import HROOT.Hist.TGraph.RawType
import HROOT.Hist.TGraph.FFI
import HROOT.Hist.TGraph.Interface
import HROOT.Hist.TGraph.Cast
import HROOT.Core.TClass.RawType
import HROOT.Core.TClass.Cast
import HROOT.Core.TClass.Interface
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.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 ITGraph TGraph where
  apply = xform1 c_tgraph_apply
  chisquare = xform1 c_tgraph_chisquare
  drawGraph = xform4 c_tgraph_drawgraph
  drawPanelTGraph = xform0 c_tgraph_drawpaneltgraph
  expand = xform2 c_tgraph_expand
  fitPanelTGraph = xform0 c_tgraph_fitpaneltgraph
  getCorrelationFactorTGraph = xform0 c_tgraph_getcorrelationfactortgraph
  getCovarianceTGraph = xform0 c_tgraph_getcovariancetgraph
  getMeanTGraph = xform1 c_tgraph_getmeantgraph
  getRMSTGraph = xform1 c_tgraph_getrmstgraph
  getErrorX = xform1 c_tgraph_geterrorx
  getErrorY = xform1 c_tgraph_geterrory
  getErrorXhigh = xform1 c_tgraph_geterrorxhigh
  getErrorXlow = xform1 c_tgraph_geterrorxlow
  getErrorYhigh = xform1 c_tgraph_geterroryhigh
  getErrorYlow = xform1 c_tgraph_geterrorylow
  initExpo = xform2 c_tgraph_initexpo
  initGaus = xform2 c_tgraph_initgaus
  initPolynom = xform2 c_tgraph_initpolynom
  insertPoint = xform0 c_tgraph_insertpoint
  integralTGraph = xform2 c_tgraph_integraltgraph
  isEditable = xform0 c_tgraph_iseditable
  isInsideTGraph = xform2 c_tgraph_isinsidetgraph
  leastSquareFit = xform4 c_tgraph_leastsquarefit
  paintStats = xform1 c_tgraph_paintstats
  removePoint = xform1 c_tgraph_removepoint
  setEditable = xform1 c_tgraph_seteditable
  setHistogram = xform1 c_tgraph_sethistogram
  setMaximumTGraph = xform1 c_tgraph_setmaximumtgraph
  setMinimumTGraph = xform1 c_tgraph_setminimumtgraph
  set = xform1 c_tgraph_set
  setPoint = xform3 c_tgraph_setpoint
instance ITNamed TGraph where
  setName = xform1 c_tgraph_setname
  setNameTitle = xform2 c_tgraph_setnametitle
  setTitle = xform1 c_tgraph_settitle
instance ITAttLine TGraph where
  getLineColor = xform0 c_tgraph_getlinecolor
  getLineStyle = xform0 c_tgraph_getlinestyle
  getLineWidth = xform0 c_tgraph_getlinewidth
  resetAttLine = xform1 c_tgraph_resetattline
  setLineAttributes = xform0 c_tgraph_setlineattributes
  setLineColor = xform1 c_tgraph_setlinecolor
  setLineStyle = xform1 c_tgraph_setlinestyle
  setLineWidth = xform1 c_tgraph_setlinewidth
instance ITAttFill TGraph where
  setFillColor = xform1 c_tgraph_setfillcolor
  setFillStyle = xform1 c_tgraph_setfillstyle
instance ITAttMarker TGraph where
  getMarkerColor = xform0 c_tgraph_getmarkercolor
  getMarkerStyle = xform0 c_tgraph_getmarkerstyle
  getMarkerSize = xform0 c_tgraph_getmarkersize
  resetAttMarker = xform1 c_tgraph_resetattmarker
  setMarkerAttributes = xform0 c_tgraph_setmarkerattributes
  setMarkerColor = xform1 c_tgraph_setmarkercolor
  setMarkerStyle = xform1 c_tgraph_setmarkerstyle
  setMarkerSize = xform1 c_tgraph_setmarkersize
instance ITObject TGraph where
  draw = xform1 c_tgraph_draw
  findObject = xform1 c_tgraph_findobject
  getName = xform0 c_tgraph_getname
  isA = xform0 c_tgraph_isa
  paint = xform1 c_tgraph_paint
  printObj = xform1 c_tgraph_printobj
  saveAs = xform2 c_tgraph_saveas
  write = xform3 c_tgraph_write
instance IDeletable TGraph where
  delete = xform0 c_tgraph_delete

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


newTGraph :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO TGraph
newTGraph = xform2 c_tgraph_newtgraph

tGraphGetEditable :: TGraph -> IO CInt
tGraphGetEditable = xform0 c_tgraph_tgraphgeteditable

tGraphGetFunction :: TGraph -> CString -> IO TF1
tGraphGetFunction = xform1 c_tgraph_tgraphgetfunction

tGraphGetHistogram :: TGraph -> IO TH1F
tGraphGetHistogram = xform0 c_tgraph_tgraphgethistogram

tGraphGetMaxSize :: TGraph -> IO CInt
tGraphGetMaxSize = xform0 c_tgraph_tgraphgetmaxsize

tGraphGetN :: TGraph -> IO CInt
tGraphGetN = xform0 c_tgraph_tgraphgetn

tGraphGetMaximum :: TGraph -> IO CDouble
tGraphGetMaximum = xform0 c_tgraph_tgraphgetmaximum

tGraphGetMinimum :: TGraph -> IO CDouble
tGraphGetMinimum = xform0 c_tgraph_tgraphgetminimum

tGraphGetXaxis :: TGraph -> IO TAxis
tGraphGetXaxis = xform0 c_tgraph_tgraphgetxaxis

tGraphGetYaxis :: TGraph -> IO TAxis
tGraphGetYaxis = xform0 c_tgraph_tgraphgetyaxis

tGraphPaintGraph :: TGraph -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
tGraphPaintGraph = xform4 c_tgraph_tgraphpaintgraph

tGraphPaintGrapHist :: TGraph -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CString -> IO ()
tGraphPaintGrapHist = xform4 c_tgraph_tgraphpaintgraphist



instance FPtr (Exist TGraph) where
  type Raw (Exist TGraph) = RawTGraph
  get_fptr (ETGraph obj) = castForeignPtr (get_fptr obj)
  cast_fptr_to_obj fptr = ETGraph (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraph) :: TGraph)