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

module HROOT.Hist.TH3C.Implementation where


import FFICXX.Runtime.Cast

import HROOT.Hist.TH3C.RawType
import HROOT.Hist.TH3C.FFI
import HROOT.Hist.TH3C.Interface
import HROOT.Hist.TH3C.Cast
import HROOT.Hist.TH1D.RawType
import HROOT.Hist.TH1D.Cast
import HROOT.Hist.TH1D.Interface
import HROOT.Hist.TF1.RawType
import HROOT.Hist.TF1.Cast
import HROOT.Hist.TF1.Interface
import HROOT.Core.TDirectory.RawType
import HROOT.Core.TDirectory.Cast
import HROOT.Core.TDirectory.Interface
import HROOT.Core.TArrayD.RawType
import HROOT.Core.TArrayD.Cast
import HROOT.Core.TArrayD.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.TH3.RawType
import HROOT.Hist.TH3.Cast
import HROOT.Hist.TH3.Interface
import HROOT.Core.TArrayC.RawType
import HROOT.Core.TArrayC.Cast
import HROOT.Core.TArrayC.Interface
import HROOT.Hist.TH1.RawType
import HROOT.Hist.TH1.Cast
import HROOT.Hist.TH1.Interface
import HROOT.Core.TAtt3D.RawType
import HROOT.Core.TAtt3D.Cast
import HROOT.Core.TAtt3D.Interface
import HROOT.Core.TObject.RawType
import HROOT.Core.TObject.Cast
import HROOT.Core.TObject.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.Deletable.RawType
import HROOT.Core.Deletable.Cast
import HROOT.Core.Deletable.Interface
import HROOT.Core.TArray.RawType
import HROOT.Core.TArray.Cast
import HROOT.Core.TArray.Interface

import Data.Word
import Foreign.C
import Foreign.Ptr 
import Foreign.ForeignPtr

import System.IO.Unsafe


instance ITH3C TH3C where
instance ITH3 TH3C where
  fill3 = xform3 c_th3c_fill3
  fill3w = xform4 c_th3c_fill3w
  fitSlicesZ = xform7 c_th3c_fitslicesz
  getCorrelationFactor3 = xform2 c_th3c_getcorrelationfactor3
  getCovariance3 = xform2 c_th3c_getcovariance3
  rebinX3 = xform2 c_th3c_rebinx3
  rebinY3 = xform2 c_th3c_rebiny3
  rebinZ3 = xform2 c_th3c_rebinz3
  rebin3D = xform4 c_th3c_rebin3d
instance ITArrayC TH3C where
instance ITH1 TH3C where
  add = xform2 c_th3c_add
  addBinContent = xform2 c_th3c_addbincontent
  chi2Test = xform3 c_th3c_chi2test
  computeIntegral = xform0 c_th3c_computeintegral
  directoryAutoAdd = xform1 c_th3c_directoryautoadd
  divide = xform5 c_th3c_divide
  drawCopyTH1 = xform1 c_th3c_drawcopyth1
  drawNormalized = xform2 c_th3c_drawnormalized
  drawPanelTH1 = xform0 c_th3c_drawpanelth1
  bufferEmpty = xform1 c_th3c_bufferempty
  evalF = xform2 c_th3c_evalf
  fFT = xform2 c_th3c_fft
  fill1 = xform1 c_th3c_fill1
  fill1w = xform2 c_th3c_fill1w
  fillN1 = xform4 c_th3c_filln1
  fillRandom = xform2 c_th3c_fillrandom
  findBin = xform3 c_th3c_findbin
  findFixBin = xform3 c_th3c_findfixbin
  findFirstBinAbove = xform2 c_th3c_findfirstbinabove
  findLastBinAbove = xform2 c_th3c_findlastbinabove
  fitPanelTH1 = xform0 c_th3c_fitpanelth1
  getNdivisionA = xform1 c_th3c_getndivisiona
  getAxisColorA = xform1 c_th3c_getaxiscolora
  getLabelColorA = xform1 c_th3c_getlabelcolora
  getLabelFontA = xform1 c_th3c_getlabelfonta
  getLabelOffsetA = xform1 c_th3c_getlabeloffseta
  getLabelSizeA = xform1 c_th3c_getlabelsizea
  getTitleFontA = xform1 c_th3c_gettitlefonta
  getTitleOffsetA = xform1 c_th3c_gettitleoffseta
  getTitleSizeA = xform1 c_th3c_gettitlesizea
  getTickLengthA = xform1 c_th3c_getticklengtha
  getBarOffset = xform0 c_th3c_getbaroffset
  getBarWidth = xform0 c_th3c_getbarwidth
  getContour = xform1 c_th3c_getcontour
  getContourLevel = xform1 c_th3c_getcontourlevel
  getContourLevelPad = xform1 c_th3c_getcontourlevelpad
  getBin = xform3 c_th3c_getbin
  getBinCenter = xform1 c_th3c_getbincenter
  getBinContent1 = xform1 c_th3c_getbincontent1
  getBinContent2 = xform2 c_th3c_getbincontent2
  getBinContent3 = xform3 c_th3c_getbincontent3
  getBinError1 = xform1 c_th3c_getbinerror1
  getBinError2 = xform2 c_th3c_getbinerror2
  getBinError3 = xform3 c_th3c_getbinerror3
  getBinLowEdge = xform1 c_th3c_getbinlowedge
  getBinWidth = xform1 c_th3c_getbinwidth
  getCellContent = xform2 c_th3c_getcellcontent
  getCellError = xform2 c_th3c_getcellerror
  getEntries = xform0 c_th3c_getentries
  getEffectiveEntries = xform0 c_th3c_geteffectiveentries
  getFunction = xform1 c_th3c_getfunction
  getDimension = xform0 c_th3c_getdimension
  getKurtosis = xform1 c_th3c_getkurtosis
  getLowEdge = xform1 c_th3c_getlowedge
  getMaximumTH1 = xform1 c_th3c_getmaximumth1
  getMaximumBin = xform0 c_th3c_getmaximumbin
  getMaximumStored = xform0 c_th3c_getmaximumstored
  getMinimumTH1 = xform1 c_th3c_getminimumth1
  getMinimumBin = xform0 c_th3c_getminimumbin
  getMinimumStored = xform0 c_th3c_getminimumstored
  getMean = xform1 c_th3c_getmean
  getMeanError = xform1 c_th3c_getmeanerror
  getNbinsX = xform0 c_th3c_getnbinsx
  getNbinsY = xform0 c_th3c_getnbinsy
  getNbinsZ = xform0 c_th3c_getnbinsz
  getQuantilesTH1 = xform3 c_th3c_getquantilesth1
  getRandom = xform0 c_th3c_getrandom
  getStats = xform1 c_th3c_getstats
  getSumOfWeights = xform0 c_th3c_getsumofweights
  getSumw2 = xform0 c_th3c_getsumw2
  getSumw2N = xform0 c_th3c_getsumw2n
  getRMS = xform1 c_th3c_getrms
  getRMSError = xform1 c_th3c_getrmserror
  getSkewness = xform1 c_th3c_getskewness
  integral1 = xform3 c_th3c_integral1
  interpolate1 = xform1 c_th3c_interpolate1
  interpolate2 = xform2 c_th3c_interpolate2
  interpolate3 = xform3 c_th3c_interpolate3
  kolmogorovTest = xform2 c_th3c_kolmogorovtest
  labelsDeflate = xform1 c_th3c_labelsdeflate
  labelsInflate = xform1 c_th3c_labelsinflate
  labelsOption = xform2 c_th3c_labelsoption
  multiflyF = xform2 c_th3c_multiflyf
  multiply = xform5 c_th3c_multiply
  putStats = xform1 c_th3c_putstats
  rebin = xform3 c_th3c_rebin
  rebinAxis = xform2 c_th3c_rebinaxis
  rebuild = xform1 c_th3c_rebuild
  recursiveRemove = xform1 c_th3c_recursiveremove
  reset = xform1 c_th3c_reset
  resetStats = xform0 c_th3c_resetstats
  scale = xform2 c_th3c_scale
  setAxisColorA = xform2 c_th3c_setaxiscolora
  setAxisRange = xform3 c_th3c_setaxisrange
  setBarOffset = xform1 c_th3c_setbaroffset
  setBarWidth = xform1 c_th3c_setbarwidth
  setBinContent1 = xform2 c_th3c_setbincontent1
  setBinContent2 = xform3 c_th3c_setbincontent2
  setBinContent3 = xform4 c_th3c_setbincontent3
  setBinError1 = xform2 c_th3c_setbinerror1
  setBinError2 = xform3 c_th3c_setbinerror2
  setBinError3 = xform4 c_th3c_setbinerror3
  setBins1 = xform2 c_th3c_setbins1
  setBins2 = xform4 c_th3c_setbins2
  setBins3 = xform6 c_th3c_setbins3
  setBinsLength = xform1 c_th3c_setbinslength
  setBuffer = xform2 c_th3c_setbuffer
  setCellContent = xform3 c_th3c_setcellcontent
  setContent = xform1 c_th3c_setcontent
  setContour = xform2 c_th3c_setcontour
  setContourLevel = xform2 c_th3c_setcontourlevel
  setDirectory = xform1 c_th3c_setdirectory
  setEntries = xform1 c_th3c_setentries
  setError = xform1 c_th3c_seterror
  setLabelColorA = xform2 c_th3c_setlabelcolora
  setLabelSizeA = xform2 c_th3c_setlabelsizea
  setLabelFontA = xform2 c_th3c_setlabelfonta
  setLabelOffsetA = xform2 c_th3c_setlabeloffseta
  setMaximum = xform1 c_th3c_setmaximum
  setMinimum = xform1 c_th3c_setminimum
  setNormFactor = xform1 c_th3c_setnormfactor
  setStats = xform1 c_th3c_setstats
  setOption = xform1 c_th3c_setoption
  setXTitle = xform1 c_th3c_setxtitle
  setYTitle = xform1 c_th3c_setytitle
  setZTitle = xform1 c_th3c_setztitle
  showBackground = xform2 c_th3c_showbackground
  showPeaks = xform3 c_th3c_showpeaks
  smooth = xform2 c_th3c_smooth
  sumw2 = xform0 c_th3c_sumw2
instance ITAtt3D TH3C where
instance ITObject TH3C where
  draw = xform1 c_th3c_draw
  findObject = xform1 c_th3c_findobject
  getName = xform0 c_th3c_getname
  isA = xform0 c_th3c_isa
  paint = xform1 c_th3c_paint
  printObj = xform1 c_th3c_printobj
  saveAs = xform2 c_th3c_saveas
  write = xform3 c_th3c_write
instance ITAttLine TH3C where
  getLineColor = xform0 c_th3c_getlinecolor
  getLineStyle = xform0 c_th3c_getlinestyle
  getLineWidth = xform0 c_th3c_getlinewidth
  resetAttLine = xform1 c_th3c_resetattline
  setLineAttributes = xform0 c_th3c_setlineattributes
  setLineColor = xform1 c_th3c_setlinecolor
  setLineStyle = xform1 c_th3c_setlinestyle
  setLineWidth = xform1 c_th3c_setlinewidth
instance ITAttFill TH3C where
  setFillColor = xform1 c_th3c_setfillcolor
  setFillStyle = xform1 c_th3c_setfillstyle
instance ITAttMarker TH3C where
  getMarkerColor = xform0 c_th3c_getmarkercolor
  getMarkerStyle = xform0 c_th3c_getmarkerstyle
  getMarkerSize = xform0 c_th3c_getmarkersize
  resetAttMarker = xform1 c_th3c_resetattmarker
  setMarkerAttributes = xform0 c_th3c_setmarkerattributes
  setMarkerColor = xform1 c_th3c_setmarkercolor
  setMarkerStyle = xform1 c_th3c_setmarkerstyle
  setMarkerSize = xform1 c_th3c_setmarkersize
instance IDeletable TH3C where
  delete = xform0 c_th3c_delete
instance ITArray TH3C where

instance ITH3C (Exist TH3C) where

instance ITH3 (Exist TH3C) where
  fill3 (ETH3C x) = fill3 x
  fill3w (ETH3C x) = fill3w x
  fitSlicesZ (ETH3C x) = fitSlicesZ x
  getCorrelationFactor3 (ETH3C x) = getCorrelationFactor3 x
  getCovariance3 (ETH3C x) = getCovariance3 x
  rebinX3 (ETH3C x) = rebinX3 x
  rebinY3 (ETH3C x) = rebinY3 x
  rebinZ3 (ETH3C x) = rebinZ3 x
  rebin3D (ETH3C x) = rebin3D x
instance ITArrayC (Exist TH3C) where

instance ITH1 (Exist TH3C) where
  add (ETH3C x) = add x
  addBinContent (ETH3C x) = addBinContent x
  chi2Test (ETH3C x) = chi2Test x
  computeIntegral (ETH3C x) = computeIntegral x
  directoryAutoAdd (ETH3C x) = directoryAutoAdd x
  divide (ETH3C x) = divide x
  drawCopyTH1 (ETH3C x) a1 = return . ETH3C =<< drawCopyTH1 x a1
  drawNormalized (ETH3C x) = drawNormalized x
  drawPanelTH1 (ETH3C x) = drawPanelTH1 x
  bufferEmpty (ETH3C x) = bufferEmpty x
  evalF (ETH3C x) = evalF x
  fFT (ETH3C x) = fFT x
  fill1 (ETH3C x) = fill1 x
  fill1w (ETH3C x) = fill1w x
  fillN1 (ETH3C x) = fillN1 x
  fillRandom (ETH3C x) = fillRandom x
  findBin (ETH3C x) = findBin x
  findFixBin (ETH3C x) = findFixBin x
  findFirstBinAbove (ETH3C x) = findFirstBinAbove x
  findLastBinAbove (ETH3C x) = findLastBinAbove x
  fitPanelTH1 (ETH3C x) = fitPanelTH1 x
  getNdivisionA (ETH3C x) = getNdivisionA x
  getAxisColorA (ETH3C x) = getAxisColorA x
  getLabelColorA (ETH3C x) = getLabelColorA x
  getLabelFontA (ETH3C x) = getLabelFontA x
  getLabelOffsetA (ETH3C x) = getLabelOffsetA x
  getLabelSizeA (ETH3C x) = getLabelSizeA x
  getTitleFontA (ETH3C x) = getTitleFontA x
  getTitleOffsetA (ETH3C x) = getTitleOffsetA x
  getTitleSizeA (ETH3C x) = getTitleSizeA x
  getTickLengthA (ETH3C x) = getTickLengthA x
  getBarOffset (ETH3C x) = getBarOffset x
  getBarWidth (ETH3C x) = getBarWidth x
  getContour (ETH3C x) = getContour x
  getContourLevel (ETH3C x) = getContourLevel x
  getContourLevelPad (ETH3C x) = getContourLevelPad x
  getBin (ETH3C x) = getBin x
  getBinCenter (ETH3C x) = getBinCenter x
  getBinContent1 (ETH3C x) = getBinContent1 x
  getBinContent2 (ETH3C x) = getBinContent2 x
  getBinContent3 (ETH3C x) = getBinContent3 x
  getBinError1 (ETH3C x) = getBinError1 x
  getBinError2 (ETH3C x) = getBinError2 x
  getBinError3 (ETH3C x) = getBinError3 x
  getBinLowEdge (ETH3C x) = getBinLowEdge x
  getBinWidth (ETH3C x) = getBinWidth x
  getCellContent (ETH3C x) = getCellContent x
  getCellError (ETH3C x) = getCellError x
  getEntries (ETH3C x) = getEntries x
  getEffectiveEntries (ETH3C x) = getEffectiveEntries x
  getFunction (ETH3C x) = getFunction x
  getDimension (ETH3C x) = getDimension x
  getKurtosis (ETH3C x) = getKurtosis x
  getLowEdge (ETH3C x) = getLowEdge x
  getMaximumTH1 (ETH3C x) = getMaximumTH1 x
  getMaximumBin (ETH3C x) = getMaximumBin x
  getMaximumStored (ETH3C x) = getMaximumStored x
  getMinimumTH1 (ETH3C x) = getMinimumTH1 x
  getMinimumBin (ETH3C x) = getMinimumBin x
  getMinimumStored (ETH3C x) = getMinimumStored x
  getMean (ETH3C x) = getMean x
  getMeanError (ETH3C x) = getMeanError x
  getNbinsX (ETH3C x) = getNbinsX x
  getNbinsY (ETH3C x) = getNbinsY x
  getNbinsZ (ETH3C x) = getNbinsZ x
  getQuantilesTH1 (ETH3C x) = getQuantilesTH1 x
  getRandom (ETH3C x) = getRandom x
  getStats (ETH3C x) = getStats x
  getSumOfWeights (ETH3C x) = getSumOfWeights x
  getSumw2 (ETH3C x) = getSumw2 x
  getSumw2N (ETH3C x) = getSumw2N x
  getRMS (ETH3C x) = getRMS x
  getRMSError (ETH3C x) = getRMSError x
  getSkewness (ETH3C x) = getSkewness x
  integral1 (ETH3C x) = integral1 x
  interpolate1 (ETH3C x) = interpolate1 x
  interpolate2 (ETH3C x) = interpolate2 x
  interpolate3 (ETH3C x) = interpolate3 x
  kolmogorovTest (ETH3C x) = kolmogorovTest x
  labelsDeflate (ETH3C x) = labelsDeflate x
  labelsInflate (ETH3C x) = labelsInflate x
  labelsOption (ETH3C x) = labelsOption x
  multiflyF (ETH3C x) = multiflyF x
  multiply (ETH3C x) = multiply x
  putStats (ETH3C x) = putStats x
  rebin (ETH3C x) = rebin x
  rebinAxis (ETH3C x) = rebinAxis x
  rebuild (ETH3C x) = rebuild x
  recursiveRemove (ETH3C x) = recursiveRemove x
  reset (ETH3C x) = reset x
  resetStats (ETH3C x) = resetStats x
  scale (ETH3C x) = scale x
  setAxisColorA (ETH3C x) = setAxisColorA x
  setAxisRange (ETH3C x) = setAxisRange x
  setBarOffset (ETH3C x) = setBarOffset x
  setBarWidth (ETH3C x) = setBarWidth x
  setBinContent1 (ETH3C x) = setBinContent1 x
  setBinContent2 (ETH3C x) = setBinContent2 x
  setBinContent3 (ETH3C x) = setBinContent3 x
  setBinError1 (ETH3C x) = setBinError1 x
  setBinError2 (ETH3C x) = setBinError2 x
  setBinError3 (ETH3C x) = setBinError3 x
  setBins1 (ETH3C x) = setBins1 x
  setBins2 (ETH3C x) = setBins2 x
  setBins3 (ETH3C x) = setBins3 x
  setBinsLength (ETH3C x) = setBinsLength x
  setBuffer (ETH3C x) = setBuffer x
  setCellContent (ETH3C x) = setCellContent x
  setContent (ETH3C x) = setContent x
  setContour (ETH3C x) = setContour x
  setContourLevel (ETH3C x) = setContourLevel x
  setDirectory (ETH3C x) = setDirectory x
  setEntries (ETH3C x) = setEntries x
  setError (ETH3C x) = setError x
  setLabelColorA (ETH3C x) = setLabelColorA x
  setLabelSizeA (ETH3C x) = setLabelSizeA x
  setLabelFontA (ETH3C x) = setLabelFontA x
  setLabelOffsetA (ETH3C x) = setLabelOffsetA x
  setMaximum (ETH3C x) = setMaximum x
  setMinimum (ETH3C x) = setMinimum x
  setNormFactor (ETH3C x) = setNormFactor x
  setStats (ETH3C x) = setStats x
  setOption (ETH3C x) = setOption x
  setXTitle (ETH3C x) = setXTitle x
  setYTitle (ETH3C x) = setYTitle x
  setZTitle (ETH3C x) = setZTitle x
  showBackground (ETH3C x) = showBackground x
  showPeaks (ETH3C x) = showPeaks x
  smooth (ETH3C x) = smooth x
  sumw2 (ETH3C x) = sumw2 x
instance ITAtt3D (Exist TH3C) where

instance ITObject (Exist TH3C) where
  draw (ETH3C x) = draw x
  findObject (ETH3C x) = findObject x
  getName (ETH3C x) = getName x
  isA (ETH3C x) = isA x
  paint (ETH3C x) = paint x
  printObj (ETH3C x) = printObj x
  saveAs (ETH3C x) = saveAs x
  write (ETH3C x) = write x
instance ITAttLine (Exist TH3C) where
  getLineColor (ETH3C x) = getLineColor x
  getLineStyle (ETH3C x) = getLineStyle x
  getLineWidth (ETH3C x) = getLineWidth x
  resetAttLine (ETH3C x) = resetAttLine x
  setLineAttributes (ETH3C x) = setLineAttributes x
  setLineColor (ETH3C x) = setLineColor x
  setLineStyle (ETH3C x) = setLineStyle x
  setLineWidth (ETH3C x) = setLineWidth x
instance ITAttFill (Exist TH3C) where
  setFillColor (ETH3C x) = setFillColor x
  setFillStyle (ETH3C x) = setFillStyle x
instance ITAttMarker (Exist TH3C) where
  getMarkerColor (ETH3C x) = getMarkerColor x
  getMarkerStyle (ETH3C x) = getMarkerStyle x
  getMarkerSize (ETH3C x) = getMarkerSize x
  resetAttMarker (ETH3C x) = resetAttMarker x
  setMarkerAttributes (ETH3C x) = setMarkerAttributes x
  setMarkerColor (ETH3C x) = setMarkerColor x
  setMarkerStyle (ETH3C x) = setMarkerStyle x
  setMarkerSize (ETH3C x) = setMarkerSize x
instance IDeletable (Exist TH3C) where
  delete (ETH3C x) = delete x
instance ITArray (Exist TH3C) where








instance FPtr (Exist TH3C) where
  type Raw (Exist TH3C) = RawTH3C
  get_fptr (ETH3C obj) = castForeignPtr (get_fptr obj)
  cast_fptr_to_obj fptr = ETH3C (cast_fptr_to_obj (fptr :: ForeignPtr RawTH3C) :: TH3C)