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

module HROOT.Class.TGraphAsymmErrors.Implementation where


import HROOT.TypeCast

import HROOT.Class.TGraphAsymmErrors.RawType
import HROOT.Class.TGraphAsymmErrors.FFI
import HROOT.Class.TGraphAsymmErrors.Interface
import HROOT.Class.TGraphAsymmErrors.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.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 ITGraphAsymmErrors TGraphAsymmErrors where
instance ITGraph TGraphAsymmErrors where
  apply = xform1 c_tgraphasymmerrors_apply
  chisquare = xform1 c_tgraphasymmerrors_chisquare
  drawGraph = xform4 c_tgraphasymmerrors_drawgraph
  drawPanelTGraph = xform0 c_tgraphasymmerrors_drawpaneltgraph
  expand = xform2 c_tgraphasymmerrors_expand
  fitPanelTGraph = xform0 c_tgraphasymmerrors_fitpaneltgraph
  getCorrelationFactorTGraph = xform0 c_tgraphasymmerrors_getcorrelationfactortgraph
  getCovarianceTGraph = xform0 c_tgraphasymmerrors_getcovariancetgraph
  getMeanTGraph = xform1 c_tgraphasymmerrors_getmeantgraph
  getRMSTGraph = xform1 c_tgraphasymmerrors_getrmstgraph
  getErrorX = xform1 c_tgraphasymmerrors_geterrorx
  getErrorY = xform1 c_tgraphasymmerrors_geterrory
  getErrorXhigh = xform1 c_tgraphasymmerrors_geterrorxhigh
  getErrorXlow = xform1 c_tgraphasymmerrors_geterrorxlow
  getErrorYhigh = xform1 c_tgraphasymmerrors_geterroryhigh
  getErrorYlow = xform1 c_tgraphasymmerrors_geterrorylow
  initExpo = xform2 c_tgraphasymmerrors_initexpo
  initGaus = xform2 c_tgraphasymmerrors_initgaus
  initPolynom = xform2 c_tgraphasymmerrors_initpolynom
  insertPoint = xform0 c_tgraphasymmerrors_insertpoint
  integralTGraph = xform2 c_tgraphasymmerrors_integraltgraph
  isEditable = xform0 c_tgraphasymmerrors_iseditable
  isInsideTGraph = xform2 c_tgraphasymmerrors_isinsidetgraph
  leastSquareFit = xform4 c_tgraphasymmerrors_leastsquarefit
  paintStats = xform1 c_tgraphasymmerrors_paintstats
  removePoint = xform1 c_tgraphasymmerrors_removepoint
  setEditable = xform1 c_tgraphasymmerrors_seteditable
  setHistogram = xform1 c_tgraphasymmerrors_sethistogram
  setMaximumTGraph = xform1 c_tgraphasymmerrors_setmaximumtgraph
  setMinimumTGraph = xform1 c_tgraphasymmerrors_setminimumtgraph
  set = xform1 c_tgraphasymmerrors_set
  setPoint = xform3 c_tgraphasymmerrors_setpoint
instance ITNamed TGraphAsymmErrors where
  setName = xform1 c_tgraphasymmerrors_setname
  setNameTitle = xform2 c_tgraphasymmerrors_setnametitle
  setTitle = xform1 c_tgraphasymmerrors_settitle
instance ITAttLine TGraphAsymmErrors where
  getLineColor = xform0 c_tgraphasymmerrors_getlinecolor
  getLineStyle = xform0 c_tgraphasymmerrors_getlinestyle
  getLineWidth = xform0 c_tgraphasymmerrors_getlinewidth
  resetAttLine = xform1 c_tgraphasymmerrors_resetattline
  setLineAttributes = xform0 c_tgraphasymmerrors_setlineattributes
  setLineColor = xform1 c_tgraphasymmerrors_setlinecolor
  setLineStyle = xform1 c_tgraphasymmerrors_setlinestyle
  setLineWidth = xform1 c_tgraphasymmerrors_setlinewidth
instance ITAttFill TGraphAsymmErrors where
  setFillColor = xform1 c_tgraphasymmerrors_setfillcolor
  setFillStyle = xform1 c_tgraphasymmerrors_setfillstyle
instance ITAttMarker TGraphAsymmErrors where
  getMarkerColor = xform0 c_tgraphasymmerrors_getmarkercolor
  getMarkerStyle = xform0 c_tgraphasymmerrors_getmarkerstyle
  getMarkerSize = xform0 c_tgraphasymmerrors_getmarkersize
  resetAttMarker = xform1 c_tgraphasymmerrors_resetattmarker
  setMarkerAttributes = xform0 c_tgraphasymmerrors_setmarkerattributes
  setMarkerColor = xform1 c_tgraphasymmerrors_setmarkercolor
  setMarkerStyle = xform1 c_tgraphasymmerrors_setmarkerstyle
  setMarkerSize = xform1 c_tgraphasymmerrors_setmarkersize
instance ITObject TGraphAsymmErrors where
  draw = xform1 c_tgraphasymmerrors_draw
  findObject = xform1 c_tgraphasymmerrors_findobject
  getName = xform0 c_tgraphasymmerrors_getname
  isA = xform0 c_tgraphasymmerrors_isa
  isFolder = xform0 c_tgraphasymmerrors_isfolder
  isEqual = xform1 c_tgraphasymmerrors_isequal
  isSortable = xform0 c_tgraphasymmerrors_issortable
  paint = xform1 c_tgraphasymmerrors_paint
  printObj = xform1 c_tgraphasymmerrors_printobj
  recursiveRemove = xform1 c_tgraphasymmerrors_recursiveremove
  saveAs = xform2 c_tgraphasymmerrors_saveas
  useCurrentStyle = xform0 c_tgraphasymmerrors_usecurrentstyle
  write = xform3 c_tgraphasymmerrors_write
instance IDeletable TGraphAsymmErrors where
  delete = xform0 c_tgraphasymmerrors_delete

instance ITGraphAsymmErrors (Exist TGraphAsymmErrors) where

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


newTGraphAsymmErrors :: Int -> [Double] -> [Double] -> [Double] -> [Double] -> [Double] -> [Double] -> IO TGraphAsymmErrors
newTGraphAsymmErrors = xform6 c_tgraphasymmerrors_newtgraphasymmerrors



instance FPtr (Exist TGraphAsymmErrors) where
  type Raw (Exist TGraphAsymmErrors) = RawTGraphAsymmErrors
  get_fptr (ETGraphAsymmErrors obj) = castForeignPtr (get_fptr obj)
  cast_fptr_to_obj fptr = ETGraphAsymmErrors (cast_fptr_to_obj (fptr :: ForeignPtr RawTGraphAsymmErrors) :: TGraphAsymmErrors)