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

module HROOT.Class.TGraphPolar.Implementation where


import HROOT.TypeCast

import HROOT.Class.TGraphPolar.RawType
import HROOT.Class.TGraphPolar.FFI
import HROOT.Class.TGraphPolar.Interface
import HROOT.Class.TGraphPolar.Cast
import HROOT.Class.TF1.RawType
import HROOT.Class.TF1.Cast
import HROOT.Class.TF1.Interface
import HROOT.Class.TH1F.RawType
import HROOT.Class.TH1F.Cast
import HROOT.Class.TH1F.Interface
import HROOT.Class.TList.RawType
import HROOT.Class.TList.Cast
import HROOT.Class.TList.Interface
import HROOT.Class.TAxis.RawType
import HROOT.Class.TAxis.Cast
import HROOT.Class.TAxis.Interface
import HROOT.Class.TClass.RawType
import HROOT.Class.TClass.Cast
import HROOT.Class.TClass.Interface
import HROOT.Class.TGraphErrors.RawType
import HROOT.Class.TGraphErrors.Cast
import HROOT.Class.TGraphErrors.Interface
import HROOT.Class.TGraph.RawType
import HROOT.Class.TGraph.Cast
import HROOT.Class.TGraph.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 ITGraphPolar TGraphPolar where
instance ITGraphErrors TGraphPolar where
instance ITGraph TGraphPolar where
  apply = xform1 c_tgraphpolar_apply
  chisquare = xform1 c_tgraphpolar_chisquare
  drawGraph = xform4 c_tgraphpolar_drawgraph
  drawPanelTGraph = xform0 c_tgraphpolar_drawpaneltgraph
  expand = xform2 c_tgraphpolar_expand
  fitPanelTGraph = xform0 c_tgraphpolar_fitpaneltgraph
  getCorrelationFactorTGraph = xform0 c_tgraphpolar_getcorrelationfactortgraph
  getCovarianceTGraph = xform0 c_tgraphpolar_getcovariancetgraph
  getMeanTGraph = xform1 c_tgraphpolar_getmeantgraph
  getRMSTGraph = xform1 c_tgraphpolar_getrmstgraph
  getErrorX = xform1 c_tgraphpolar_geterrorx
  getErrorY = xform1 c_tgraphpolar_geterrory
  getErrorXhigh = xform1 c_tgraphpolar_geterrorxhigh
  getErrorXlow = xform1 c_tgraphpolar_geterrorxlow
  getErrorYhigh = xform1 c_tgraphpolar_geterroryhigh
  getErrorYlow = xform1 c_tgraphpolar_geterrorylow
  initExpo = xform2 c_tgraphpolar_initexpo
  initGaus = xform2 c_tgraphpolar_initgaus
  initPolynom = xform2 c_tgraphpolar_initpolynom
  insertPoint = xform0 c_tgraphpolar_insertpoint
  integralTGraph = xform2 c_tgraphpolar_integraltgraph
  isEditable = xform0 c_tgraphpolar_iseditable
  isInsideTGraph = xform2 c_tgraphpolar_isinsidetgraph
  leastSquareFit = xform4 c_tgraphpolar_leastsquarefit
  paintStats = xform1 c_tgraphpolar_paintstats
  removePoint = xform1 c_tgraphpolar_removepoint
  setEditable = xform1 c_tgraphpolar_seteditable
  setHistogram = xform1 c_tgraphpolar_sethistogram
  setMaximumTGraph = xform1 c_tgraphpolar_setmaximumtgraph
  setMinimumTGraph = xform1 c_tgraphpolar_setminimumtgraph
  set = xform1 c_tgraphpolar_set
  setPoint = xform3 c_tgraphpolar_setpoint
instance ITNamed TGraphPolar where
  setName = xform1 c_tgraphpolar_setname
  setNameTitle = xform2 c_tgraphpolar_setnametitle
  setTitle = xform1 c_tgraphpolar_settitle
instance ITAttLine TGraphPolar where
  getLineColor = xform0 c_tgraphpolar_getlinecolor
  getLineStyle = xform0 c_tgraphpolar_getlinestyle
  getLineWidth = xform0 c_tgraphpolar_getlinewidth
  resetAttLine = xform1 c_tgraphpolar_resetattline
  setLineAttributes = xform0 c_tgraphpolar_setlineattributes
  setLineColor = xform1 c_tgraphpolar_setlinecolor
  setLineStyle = xform1 c_tgraphpolar_setlinestyle
  setLineWidth = xform1 c_tgraphpolar_setlinewidth
instance ITAttFill TGraphPolar where
  setFillColor = xform1 c_tgraphpolar_setfillcolor
  setFillStyle = xform1 c_tgraphpolar_setfillstyle
instance ITAttMarker TGraphPolar where
  getMarkerColor = xform0 c_tgraphpolar_getmarkercolor
  getMarkerStyle = xform0 c_tgraphpolar_getmarkerstyle
  getMarkerSize = xform0 c_tgraphpolar_getmarkersize
  resetAttMarker = xform1 c_tgraphpolar_resetattmarker
  setMarkerAttributes = xform0 c_tgraphpolar_setmarkerattributes
  setMarkerColor = xform1 c_tgraphpolar_setmarkercolor
  setMarkerStyle = xform1 c_tgraphpolar_setmarkerstyle
  setMarkerSize = xform1 c_tgraphpolar_setmarkersize
instance ITObject TGraphPolar where
  draw = xform1 c_tgraphpolar_draw
  findObject = xform1 c_tgraphpolar_findobject
  getName = xform0 c_tgraphpolar_getname
  isA = xform0 c_tgraphpolar_isa
  isFolder = xform0 c_tgraphpolar_isfolder
  isEqual = xform1 c_tgraphpolar_isequal
  isSortable = xform0 c_tgraphpolar_issortable
  paint = xform1 c_tgraphpolar_paint
  printObj = xform1 c_tgraphpolar_printobj
  recursiveRemove = xform1 c_tgraphpolar_recursiveremove
  saveAs = xform2 c_tgraphpolar_saveas
  useCurrentStyle = xform0 c_tgraphpolar_usecurrentstyle
  write = xform3 c_tgraphpolar_write
instance IDeletable TGraphPolar where
  delete = xform0 c_tgraphpolar_delete

instance ITGraphPolar (Exist TGraphPolar) where

instance ITGraphErrors (Exist TGraphPolar) where

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


newTGraphPolar :: Int -> [Double] -> [Double] -> [Double] -> [Double] -> IO TGraphPolar
newTGraphPolar = xform4 c_tgraphpolar_newtgraphpolar





instance FPtr (Exist TGraphPolar) where
  type Raw (Exist TGraphPolar) = RawTGraphPolar
  get_fptr (ETGraphPolar obj) = castForeignPtr (get_fptr obj)
  cast_fptr_to_obj fptr = ETGraphPolar (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraphPolar) :: TGraphPolar)