{-# LANGUAGE EmptyDataDecls, ExistentialQuantification,
  FlexibleContexts, FlexibleInstances, ForeignFunctionInterface,
  MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies,
  TypeSynonymInstances #-}
module HROOT.Hist.TF1.Interface where
import Data.Word
import Data.Int
import Foreign.C
import Foreign.Ptr
import FFICXX.Runtime.Cast
import HROOT.Hist.TF1.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TAttLine.Interface
import HROOT.Core.TAttFill.Interface
import HROOT.Core.TAttMarker.Interface
import HROOT.Core.TObject.Interface

class (ITAttLine a, ITAttFill a, ITAttMarker a) => ITF1 a where
        derivative ::
                     () => a -> CDouble -> Ptr CDouble -> CDouble -> IO CDouble
        
        derivative2 ::
                      () => a -> CDouble -> Ptr CDouble -> CDouble -> IO CDouble
        
        derivative3 ::
                      () => a -> CDouble -> Ptr CDouble -> CDouble -> IO CDouble
        
        drawCopyTF1 :: (Castable c0 CString) => a -> c0 -> IO a
        
        drawDerivative :: (Castable c0 CString) => a -> c0 -> IO TObject
        
        drawIntegral :: (Castable c0 CString) => a -> c0 -> IO TObject
        
        fixParameter :: () => a -> CInt -> CDouble -> IO ()
        
        getMaximumTF1 ::
                        () =>
                        a ->
                          CDouble -> CDouble -> CDouble -> CDouble -> CBool -> IO CDouble
        
        getMinimumTF1 ::
                        () =>
                        a ->
                          CDouble -> CDouble -> CDouble -> CDouble -> CBool -> IO CDouble
        
        getMaximumX ::
                      () =>
                      a ->
                        CDouble -> CDouble -> CDouble -> CDouble -> CBool -> IO CDouble
        
        getMinimumX ::
                      () =>
                      a ->
                        CDouble -> CDouble -> CDouble -> CDouble -> CBool -> IO CDouble
        
        getNDF :: () => a -> IO CInt
        
        getNpx :: () => a -> IO CInt
        
        getNumberFreeParameters :: () => a -> IO CInt
        
        getNumberFitPoints :: () => a -> IO CInt
        
        getParError :: () => a -> CInt -> IO CDouble
        
        getProb :: () => a -> IO CDouble
        
        getQuantilesTF1 ::
                          () => a -> CInt -> Ptr CDouble -> Ptr CDouble -> IO CInt
        
        getRandomTF1 :: () => a -> CDouble -> CDouble -> IO CDouble
        
        getSave :: () => a -> Ptr CDouble -> IO CDouble
        
        getX ::
               () =>
               a -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble
        
        getXmin :: () => a -> IO CDouble
        
        getXmax :: () => a -> IO CDouble
        
        gradientPar ::
                      () => a -> CInt -> Ptr CDouble -> CDouble -> IO CDouble
        
        initArgs :: () => a -> Ptr CDouble -> Ptr CDouble -> IO ()
        
        integralTF1 ::
                      () => a -> CDouble -> CDouble -> CDouble -> IO CDouble
        
        integralError ::
                        () =>
                        a ->
                          CDouble ->
                            CDouble -> Ptr CDouble -> Ptr CDouble -> CDouble -> IO CDouble
        
        integralFast ::
                       () =>
                       a ->
                         CInt ->
                           Ptr CDouble ->
                             Ptr CDouble ->
                               CDouble -> CDouble -> Ptr CDouble -> CDouble -> IO CDouble
        
        isInside :: () => a -> Ptr CDouble -> IO CBool
        
        releaseParameter :: () => a -> CInt -> IO ()
        
        setChisquare :: () => a -> CDouble -> IO ()
        
        setMaximumTF1 :: () => a -> CDouble -> IO ()
        
        setMinimumTF1 :: () => a -> CDouble -> IO ()
        
        setNDF :: () => a -> CInt -> IO ()
        
        setNumberFitPoints :: () => a -> CInt -> IO ()
        
        setNpx :: () => a -> CInt -> IO ()
        
        setParError :: () => a -> CInt -> CDouble -> IO ()
        
        setParErrors :: () => a -> Ptr CDouble -> IO ()
        
        setParLimits :: () => a -> CInt -> CDouble -> CDouble -> IO ()
        
        setParent :: (ITObject c0, FPtr c0) => a -> c0 -> IO ()
        
        setRange1 :: () => a -> CDouble -> CDouble -> IO ()
        
        setRange2 ::
                    () => a -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
        
        setRange3 ::
                    () =>
                    a ->
                      CDouble ->
                        CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()
        
        setSavedPoint :: () => a -> CInt -> CDouble -> IO ()
        
        moment ::
                 () =>
                 a ->
                   CDouble ->
                     CDouble -> CDouble -> Ptr CDouble -> CDouble -> IO CDouble
        
        centralMoment ::
                        () =>
                        a ->
                          CDouble ->
                            CDouble -> CDouble -> Ptr CDouble -> CDouble -> IO CDouble
        
        mean ::
               () =>
               a -> CDouble -> CDouble -> Ptr CDouble -> CDouble -> IO CDouble
        
        variance ::
                   () =>
                   a -> CDouble -> CDouble -> Ptr CDouble -> CDouble -> IO CDouble

upcastTF1 :: forall a . (FPtr a, ITF1 a) => a -> TF1
upcastTF1 :: forall a. (FPtr a, ITF1 a) => a -> TF1
upcastTF1 a
h
  = let fh :: Ptr (Raw a)
fh = a -> Ptr (Raw a)
forall a. FPtr a => a -> Ptr (Raw a)
get_fptr a
h
        Ptr RawTF1
fh2 :: Ptr RawTF1 = Ptr (Raw a) -> Ptr RawTF1
forall a b. Ptr a -> Ptr b
castPtr Ptr (Raw a)
fh
      in Ptr (Raw TF1) -> TF1
forall a. FPtr a => Ptr (Raw a) -> a
cast_fptr_to_obj Ptr (Raw TF1)
Ptr RawTF1
fh2

downcastTF1 :: forall a . (FPtr a, ITF1 a) => TF1 -> a
downcastTF1 :: forall a. (FPtr a, ITF1 a) => TF1 -> a
downcastTF1 TF1
h
  = let fh :: Ptr (Raw TF1)
fh = TF1 -> Ptr (Raw TF1)
forall a. FPtr a => a -> Ptr (Raw a)
get_fptr TF1
h
        fh2 :: Ptr (Raw a)
fh2 = Ptr RawTF1 -> Ptr (Raw a)
forall a b. Ptr a -> Ptr b
castPtr Ptr (Raw TF1)
Ptr RawTF1
fh
      in Ptr (Raw a) -> a
forall a. FPtr a => Ptr (Raw a) -> a
cast_fptr_to_obj Ptr (Raw a)
fh2