{-# LANGUAGE EmptyDataDecls, ExistentialQuantification, FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, TypeSynonymInstances #-} module HROOT.Hist.TH2.Interface where import Data.Word import Foreign.C import Foreign.Ptr 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 fill2 :: a -> CDouble -> CDouble -> IO CInt fill2w :: a -> CDouble -> CDouble -> CDouble -> IO CInt fillN2 :: a -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> (Ptr CDouble) -> CInt -> IO () fillRandom2 :: (ITH1 c0, FPtr c0) => a -> c0 -> CInt -> IO () findFirstBinAbove2 :: a -> CDouble -> CInt -> IO CInt findLastBinAbove2 :: a -> CDouble -> CInt -> IO CInt fitSlicesX :: (ITObjArray c2, FPtr c2, Castable c1 CString, ITF1 c0, FPtr c0) => a -> c0 -> CInt -> CInt -> CInt -> c1 -> c2 -> IO () fitSlicesY :: (ITObjArray c2, FPtr c2, Castable c1 CString, ITF1 c0, FPtr c0) => a -> c0 -> CInt -> CInt -> CInt -> c1 -> c2 -> IO () getCorrelationFactor2 :: a -> CInt -> CInt -> IO CDouble getCovariance2 :: a -> CInt -> CInt -> IO CDouble integral2 :: Castable c0 CString => a -> CInt -> CInt -> CInt -> CInt -> c0 -> IO CDouble rebinX2 :: Castable c0 CString => a -> CInt -> c0 -> IO TH2 rebinY2 :: Castable c0 CString => a -> CInt -> c0 -> IO TH2 rebin2D :: Castable c0 CString => a -> CInt -> CInt -> c0 -> IO TH2 setShowProjectionX :: a -> CInt -> IO () setShowProjectionY :: a -> CInt -> IO () upcastTH2 :: forall a . (FPtr a, ITH2 a) => a -> TH2 upcastTH2 h = let fh = get_fptr h fh2 :: Ptr RawTH2 = castPtr fh in cast_fptr_to_obj fh2 downcastTH2 :: forall a . (FPtr a, ITH2 a) => TH2 -> a downcastTH2 h = let fh = get_fptr h fh2 = castPtr fh in cast_fptr_to_obj fh2