{-# LANGUAGE ForeignFunctionInterface, TypeFamilies, MultiParamTypeClasses, 
             FlexibleInstances, TypeSynonymInstances, 
             EmptyDataDecls, ExistentialQuantification, ScopedTypeVariables #-}

-- module HROOT.Class.Interface where

module HROOT.Hist.TH2.Interface where


import Data.Word
import Foreign.C
import Foreign.Ptr
import Foreign.ForeignPtr
import FFICXX.Runtime.Cast

import HROOT.Hist.TH2.RawType
import HROOT.Hist.TH1D.RawType
import HROOT.Hist.TH1.Interface
import HROOT.Core.TObjArray.Interface
---- ============ ----
import {-# SOURCE #-} HROOT.Hist.TF1.Interface


class (ITH1 a) => ITH2 a where
    -- | 
    --   > Int_t    Fill(Double_t x, Double_t y);

    fill2 :: a -> CDouble -> CDouble -> IO CInt 

    fill2w :: a -> CDouble -> CDouble -> CDouble -> IO CInt 

    fillN2 :: a -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () 
    -- | 
    --   > void     FillRandom(TH1 *h, Int_t ntimes=5000);
    --   

    fillRandom2 :: (ITH1 c0, FPtr c0) => a -> c0 -> CInt -> IO () 
    -- | 
    --   > Int_t    FindFirstBinAbove(Double_t threshold=0, Int_t axis=1) const;
    --   

    findFirstBinAbove2 :: a -> CDouble -> CInt -> IO CInt 
    -- | 
    --   > Int_t    FindLastBinAbove (Double_t threshold=0, Int_t axis=1) const;
    --   

    findLastBinAbove2 :: a -> CDouble -> CInt -> IO CInt 
    -- | 
    --   > void     FitSlicesX(TF1 *f1=0,Int_t firstybin=0, Int_t lastybin=-1, Int_t cut=0, Option_t *option="QNR", TObjArray* arr = 0); // *MENU*
    --   

    fitSlicesX :: (ITObjArray c1, FPtr c1, ITF1 c0, FPtr c0) => a -> c0 -> CInt -> CInt -> CInt -> CString -> c1 -> IO () 
    -- | 
    --   > void     FitSlicesY(TF1 *f1=0,Int_t firstxbin=0, Int_t lastxbin=-1, Int_t cut=0, Option_t *option="QNR", TObjArray* arr = 0); // *MENU*
    --   

    fitSlicesY :: (ITObjArray c1, FPtr c1, ITF1 c0, FPtr c0) => a -> c0 -> CInt -> CInt -> CInt -> CString -> c1 -> IO () 

    getCorrelationFactor2 :: a -> CInt -> CInt -> IO CDouble 

    getCovariance2 :: a -> CInt -> CInt -> IO CDouble 

    integral2 :: a -> CInt -> CInt -> CInt -> CInt -> CString -> IO CDouble 

    rebinX2 :: a -> CInt -> CString -> IO TH2 

    rebinY2 :: a -> CInt -> CString -> IO TH2 
    -- | 
    --   > TH2     *Rebin2D(Int_t nxgroup=2, Int_t nygroup=2, const char *newname="");     
    --   

    rebin2D :: a -> CInt -> CInt -> CString -> IO TH2 
    -- | 
    --   > void     SetShowProjectionX(Int_t nbins);  // *MENU*
    --   

    setShowProjectionX :: a -> CInt -> IO () 
    -- | 
    --   > void     SetShowProjectionY(Int_t nbins);  // *MENU*
    --   

    setShowProjectionY :: a -> CInt -> IO () 

instance Existable TH2 where
  data Exist TH2 = forall a. (FPtr a, ITH2 a) => ETH2 a

upcastTH2 :: (FPtr a, ITH2 a) => a -> TH2
upcastTH2 h = let fh = get_fptr h
                  fh2 :: ForeignPtr RawTH2 = castForeignPtr fh
              in cast_fptr_to_obj fh2

downcastTH2 :: (FPtr a, ITH2 a) => TH2 -> a 
downcastTH2 h = let fh = get_fptr h
                    fh2 = castForeignPtr fh
                in cast_fptr_to_obj fh2