{-# LINE 1 "src/HROOT/Hist/TF1/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LINE 2 "src/HROOT/Hist/TF1/FFI.hsc" #-}

-- module HROOT.Class.FFI where

module HROOT.Hist.TF1.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Hist.TF1.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType
import HROOT.Hist.TH1.RawType
import HROOT.Hist.TAxis.RawType


{-# LINE 22 "src/HROOT/Hist/TF1/FFI.hsc" #-}

foreign import ccall "HROOTHistTF1.h TF1_Compile" c_tf1_compile 
  :: (Ptr RawTF1) -> CString -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_Clear" c_tf1_clear 
  :: (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_DefinedValue" c_tf1_definedvalue 
  :: (Ptr RawTF1) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_Eval" c_tf1_eval 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_EvalParOld" c_tf1_evalparold 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_EvalPar" c_tf1_evalpar 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_GetNdim" c_tf1_getndim 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_GetNpar" c_tf1_getnpar 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_GetNumber" c_tf1_getnumber 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_GetParNumber" c_tf1_getparnumber 
  :: (Ptr RawTF1) -> CString -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_IsLinear" c_tf1_islinear 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_IsNormalized" c_tf1_isnormalized 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_SetNumber" c_tf1_setnumber 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetParameter" c_tf1_setparameter 
  :: (Ptr RawTF1) -> CString -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetParameters" c_tf1_setparameters 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetParName" c_tf1_setparname 
  :: (Ptr RawTF1) -> CInt -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetParNames" c_tf1_setparnames 
  :: (Ptr RawTF1) -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_Update" c_tf1_update 
  :: (Ptr RawTF1) -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_GetLineColor" c_tf1_getlinecolor 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_GetLineStyle" c_tf1_getlinestyle 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_GetLineWidth" c_tf1_getlinewidth 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_ResetAttLine" c_tf1_resetattline 
  :: (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetLineAttributes" c_tf1_setlineattributes 
  :: (Ptr RawTF1) -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetLineColor" c_tf1_setlinecolor 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetLineStyle" c_tf1_setlinestyle 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetLineWidth" c_tf1_setlinewidth 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetFillColor" c_tf1_setfillcolor 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetFillStyle" c_tf1_setfillstyle 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_GetMarkerColor" c_tf1_getmarkercolor 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_GetMarkerStyle" c_tf1_getmarkerstyle 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_GetMarkerSize" c_tf1_getmarkersize 
  :: (Ptr RawTF1) -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_ResetAttMarker" c_tf1_resetattmarker 
  :: (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetMarkerAttributes" c_tf1_setmarkerattributes 
  :: (Ptr RawTF1) -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetMarkerColor" c_tf1_setmarkercolor 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetMarkerStyle" c_tf1_setmarkerstyle 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetMarkerSize" c_tf1_setmarkersize 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetName" c_tf1_setname 
  :: (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetNameTitle" c_tf1_setnametitle 
  :: (Ptr RawTF1) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetTitle" c_tf1_settitle 
  :: (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_Draw" c_tf1_draw 
  :: (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_FindObject" c_tf1_findobject 
  :: (Ptr RawTF1) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTF1.h TF1_GetName" c_tf1_getname 
  :: (Ptr RawTF1) -> IO CString

foreign import ccall "HROOTHistTF1.h TF1_IsA" c_tf1_isa 
  :: (Ptr RawTF1) -> IO (Ptr RawTClass)

foreign import ccall "HROOTHistTF1.h TF1_Paint" c_tf1_paint 
  :: (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_printObj" c_tf1_printobj 
  :: (Ptr RawTF1) -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SaveAs" c_tf1_saveas 
  :: (Ptr RawTF1) -> CString -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_Write" c_tf1_write 
  :: (Ptr RawTF1) -> CString -> CInt -> CInt -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_delete" c_tf1_delete 
  :: (Ptr RawTF1) -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_newTF1" c_tf1_newtf1 
  :: CString -> CString -> CDouble -> CDouble -> IO (Ptr RawTF1)

foreign import ccall "HROOTHistTF1.h TF1_Derivative" c_tf1_derivative 
  :: (Ptr RawTF1) -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_Derivative2" c_tf1_derivative2 
  :: (Ptr RawTF1) -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_Derivative3" c_tf1_derivative3 
  :: (Ptr RawTF1) -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_tF1DerivativeError" c_tf1_tf1derivativeerror 
  :: IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_drawCopyTF1" c_tf1_drawcopytf1 
  :: (Ptr RawTF1) -> CString -> IO (Ptr RawTF1)

foreign import ccall "HROOTHistTF1.h TF1_DrawDerivative" c_tf1_drawderivative 
  :: (Ptr RawTF1) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTF1.h TF1_DrawIntegral" c_tf1_drawintegral 
  :: (Ptr RawTF1) -> CString -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTF1.h TF1_DrawF1" c_tf1_drawf1 
  :: (Ptr RawTF1) -> CString -> CDouble -> CDouble -> CString -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_FixParameter" c_tf1_fixparameter 
  :: (Ptr RawTF1) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_tF1GetChisquare" c_tf1_tf1getchisquare 
  :: (Ptr RawTF1) -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_tF1GetHistogram" c_tf1_tf1gethistogram 
  :: (Ptr RawTF1) -> IO (Ptr RawTH1)

foreign import ccall "HROOTHistTF1.h TF1_getMaximumTF1" c_tf1_getmaximumtf1 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_getMinimumTF1" c_tf1_getminimumtf1 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_GetMaximumX" c_tf1_getmaximumx 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_GetMinimumX" c_tf1_getminimumx 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_GetNDF" c_tf1_getndf 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_GetNpx" c_tf1_getnpx 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_GetNumberFreeParameters" c_tf1_getnumberfreeparameters 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_GetNumberFitPoints" c_tf1_getnumberfitpoints 
  :: (Ptr RawTF1) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_tF1GetParent" c_tf1_tf1getparent 
  :: (Ptr RawTF1) -> IO (Ptr RawTObject)

foreign import ccall "HROOTHistTF1.h TF1_GetParError" c_tf1_getparerror 
  :: (Ptr RawTF1) -> CInt -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_GetProb" c_tf1_getprob 
  :: (Ptr RawTF1) -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_getQuantilesTF1" c_tf1_getquantilestf1 
  :: (Ptr RawTF1) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_getRandomTF1" c_tf1_getrandomtf1 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_GetSave" c_tf1_getsave 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_GetX" c_tf1_getx 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_GetXmin" c_tf1_getxmin 
  :: (Ptr RawTF1) -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_GetXmax" c_tf1_getxmax 
  :: (Ptr RawTF1) -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_tF1GetXaxis" c_tf1_tf1getxaxis 
  :: (Ptr RawTF1) -> IO (Ptr RawTAxis)

foreign import ccall "HROOTHistTF1.h TF1_tF1GetYaxis" c_tf1_tf1getyaxis 
  :: (Ptr RawTF1) -> IO (Ptr RawTAxis)

foreign import ccall "HROOTHistTF1.h TF1_tF1GetZaxis" c_tf1_tf1getzaxis 
  :: (Ptr RawTF1) -> IO (Ptr RawTAxis)

foreign import ccall "HROOTHistTF1.h TF1_GradientPar" c_tf1_gradientpar 
  :: (Ptr RawTF1) -> CInt -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_InitArgs" c_tf1_initargs 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_tF1InitStandardFunctions" c_tf1_tf1initstandardfunctions 
  :: IO ()

foreign import ccall "HROOTHistTF1.h TF1_IntegralTF1" c_tf1_integraltf1 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_IntegralError" c_tf1_integralerror 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> (Ptr CDouble) -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_IntegralFast" c_tf1_integralfast 
  :: (Ptr RawTF1) -> CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_IsInside" c_tf1_isinside 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> IO CInt

foreign import ccall "HROOTHistTF1.h TF1_ReleaseParameter" c_tf1_releaseparameter 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetChisquare" c_tf1_setchisquare 
  :: (Ptr RawTF1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_setMaximumTF1" c_tf1_setmaximumtf1 
  :: (Ptr RawTF1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_setMinimumTF1" c_tf1_setminimumtf1 
  :: (Ptr RawTF1) -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetNDF" c_tf1_setndf 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetNumberFitPoints" c_tf1_setnumberfitpoints 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetNpx" c_tf1_setnpx 
  :: (Ptr RawTF1) -> CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetParError" c_tf1_setparerror 
  :: (Ptr RawTF1) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetParErrors" c_tf1_setparerrors 
  :: (Ptr RawTF1) -> (Ptr CDouble) -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetParLimits" c_tf1_setparlimits 
  :: (Ptr RawTF1) -> CInt -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetParent" c_tf1_setparent 
  :: (Ptr RawTF1) -> (Ptr RawTObject) -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_setRange1" c_tf1_setrange1 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_setRange2" c_tf1_setrange2 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_setRange3" c_tf1_setrange3 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_SetSavedPoint" c_tf1_setsavedpoint 
  :: (Ptr RawTF1) -> CInt -> CDouble -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_tF1GetCurrent" c_tf1_tf1getcurrent 
  :: IO (Ptr RawTF1)

foreign import ccall "HROOTHistTF1.h TF1_tF1AbsValue" c_tf1_tf1absvalue 
  :: CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_tF1RejectPoint" c_tf1_tf1rejectpoint 
  :: CInt -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_tF1RejectedPoint" c_tf1_tf1rejectedpoint 
  :: IO CInt

foreign import ccall "HROOTHistTF1.h TF1_tF1SetCurrent" c_tf1_tf1setcurrent 
  :: (Ptr RawTF1) -> IO ()

foreign import ccall "HROOTHistTF1.h TF1_Moment" c_tf1_moment 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_CentralMoment" c_tf1_centralmoment 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_Mean" c_tf1_mean 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_Variance" c_tf1_variance 
  :: (Ptr RawTF1) -> CDouble -> CDouble -> (Ptr CDouble) -> CDouble -> IO CDouble

foreign import ccall "HROOTHistTF1.h TF1_tF1CalcGaussLegendreSamplingPoints" c_tf1_tf1calcgausslegendresamplingpoints 
  :: CInt -> (Ptr CDouble) -> (Ptr CDouble) -> CDouble -> IO ()