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

-- module HROOT.Class.FFI where

module HROOT.Core.TAttPad.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Core.TAttPad.RawType



{-# LINE 19 "src/HROOT/Core/TAttPad/FFI.hsc" #-}

foreign import ccall "HROOTCoreTAttPad.h TAttPad_delete" c_tattpad_delete 
  :: (Ptr RawTAttPad) -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_newTAttPad" c_tattpad_newtattpad 
  :: IO (Ptr RawTAttPad)

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetBottomMargin" c_tattpad_tattpadgetbottommargin 
  :: (Ptr RawTAttPad) -> IO CDouble

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetLeftMargin" c_tattpad_tattpadgetleftmargin 
  :: (Ptr RawTAttPad) -> IO CDouble

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetRightMargin" c_tattpad_tattpadgetrightmargin 
  :: (Ptr RawTAttPad) -> IO CDouble

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetTopMargin" c_tattpad_tattpadgettopmargin 
  :: (Ptr RawTAttPad) -> IO CDouble

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetAfile" c_tattpad_tattpadgetafile 
  :: (Ptr RawTAttPad) -> IO CDouble

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetXfile" c_tattpad_tattpadgetxfile 
  :: (Ptr RawTAttPad) -> IO CDouble

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetYfile" c_tattpad_tattpadgetyfile 
  :: (Ptr RawTAttPad) -> IO CDouble

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetAstat" c_tattpad_tattpadgetastat 
  :: (Ptr RawTAttPad) -> IO CDouble

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetXstat" c_tattpad_tattpadgetxstat 
  :: (Ptr RawTAttPad) -> IO CDouble

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetYstat" c_tattpad_tattpadgetystat 
  :: (Ptr RawTAttPad) -> IO CDouble

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetFrameFillColor" c_tattpad_tattpadgetframefillcolor 
  :: (Ptr RawTAttPad) -> IO CInt

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetFrameLineColor" c_tattpad_tattpadgetframelinecolor 
  :: (Ptr RawTAttPad) -> IO CInt

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetFrameFillStyle" c_tattpad_tattpadgetframefillstyle 
  :: (Ptr RawTAttPad) -> IO CInt

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetFrameLineStyle" c_tattpad_tattpadgetframelinestyle 
  :: (Ptr RawTAttPad) -> IO CInt

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetFrameLineWidth" c_tattpad_tattpadgetframelinewidth 
  :: (Ptr RawTAttPad) -> IO CInt

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetFrameBorderSize" c_tattpad_tattpadgetframebordersize 
  :: (Ptr RawTAttPad) -> IO CInt

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadGetFrameBorderMode" c_tattpad_tattpadgetframebordermode 
  :: (Ptr RawTAttPad) -> IO CInt

foreign import ccall "HROOTCoreTAttPad.h TAttPad_ResetAttPad" c_tattpad_resetattpad 
  :: (Ptr RawTAttPad) -> CString -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetBottomMargin" c_tattpad_setbottommargin 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetLeftMargin" c_tattpad_setleftmargin 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetRightMargin" c_tattpad_setrightmargin 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetTopMargin" c_tattpad_settopmargin 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetMargin" c_tattpad_setmargin 
  :: (Ptr RawTAttPad) -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetAfile" c_tattpad_setafile 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetXfile" c_tattpad_setxfile 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetYfile" c_tattpad_setyfile 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetAstat" c_tattpad_setastat 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetXstat" c_tattpad_setxstat 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_SetYstat" c_tattpad_setystat 
  :: (Ptr RawTAttPad) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadSetFrameFillColor" c_tattpad_tattpadsetframefillcolor 
  :: (Ptr RawTAttPad) -> CInt -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadSetFrameLineColor" c_tattpad_tattpadsetframelinecolor 
  :: (Ptr RawTAttPad) -> CInt -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadSetFrameFillStyle" c_tattpad_tattpadsetframefillstyle 
  :: (Ptr RawTAttPad) -> CInt -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadSetFrameLineStyle" c_tattpad_tattpadsetframelinestyle 
  :: (Ptr RawTAttPad) -> CInt -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadSetFrameLineWidth" c_tattpad_tattpadsetframelinewidth 
  :: (Ptr RawTAttPad) -> CInt -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadSetFrameBorderSize" c_tattpad_tattpadsetframebordersize 
  :: (Ptr RawTAttPad) -> CInt -> IO ()

foreign import ccall "HROOTCoreTAttPad.h TAttPad_tAttPadSetFrameBorderMode" c_tattpad_tattpadsetframebordermode 
  :: (Ptr RawTAttPad) -> CInt -> IO ()