{-# LINE 1 "src/HROOT/Graf/TGaxis/FFI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, InterruptibleFFI #-}
module HROOT.Graf.TGaxis.FFI where
import Data.Word
import Data.Int
import Foreign.C
import Foreign.Ptr
import HROOT.Graf.TGaxis.RawType
import HROOT.Graf.TGaxis.RawType
import HROOT.Graf.TLine.RawType
import HROOT.Core.TObject.RawType
import HROOT.Core.TClass.RawType

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_DrawLine" c_tgaxis_drawline ::
               Ptr RawTGaxis ->
                 CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTLine)

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_DrawLineNDC" c_tgaxis_drawlinendc ::
               Ptr RawTGaxis ->
                 CDouble -> CDouble -> CDouble -> CDouble -> IO (Ptr RawTLine)

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_PaintLine" c_tgaxis_paintline ::
               Ptr RawTGaxis -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_PaintLineNDC" c_tgaxis_paintlinendc ::
               Ptr RawTGaxis -> CDouble -> CDouble -> CDouble -> CDouble -> IO ()

foreign import ccall interruptible "HROOTGrafTGaxis.h TGaxis_SetX1"
               c_tgaxis_setx1 :: Ptr RawTGaxis -> CDouble -> IO ()

foreign import ccall interruptible "HROOTGrafTGaxis.h TGaxis_SetX2"
               c_tgaxis_setx2 :: Ptr RawTGaxis -> CDouble -> IO ()

foreign import ccall interruptible "HROOTGrafTGaxis.h TGaxis_SetY1"
               c_tgaxis_sety1 :: Ptr RawTGaxis -> CDouble -> IO ()

foreign import ccall interruptible "HROOTGrafTGaxis.h TGaxis_SetY2"
               c_tgaxis_sety2 :: Ptr RawTGaxis -> CDouble -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_GetTextAlign" c_tgaxis_gettextalign ::
               Ptr RawTGaxis -> IO CShort

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_GetTextAngle" c_tgaxis_gettextangle ::
               Ptr RawTGaxis -> IO CFloat

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_GetTextColor" c_tgaxis_gettextcolor ::
               Ptr RawTGaxis -> IO CShort

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_GetTextFont" c_tgaxis_gettextfont ::
               Ptr RawTGaxis -> IO CShort

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_GetTextSize" c_tgaxis_gettextsize ::
               Ptr RawTGaxis -> IO CFloat

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_ResetAttText" c_tgaxis_resetatttext ::
               Ptr RawTGaxis -> CString -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetTextAttributes"
               c_tgaxis_settextattributes :: Ptr RawTGaxis -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetTextAlign" c_tgaxis_settextalign ::
               Ptr RawTGaxis -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetTextAngle" c_tgaxis_settextangle ::
               Ptr RawTGaxis -> CFloat -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetTextColor" c_tgaxis_settextcolor ::
               Ptr RawTGaxis -> CInt -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetTextFont" c_tgaxis_settextfont ::
               Ptr RawTGaxis -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetTextSize" c_tgaxis_settextsize ::
               Ptr RawTGaxis -> CFloat -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetTextSizePixels"
               c_tgaxis_settextsizepixels :: Ptr RawTGaxis -> CInt -> IO ()

foreign import ccall interruptible "HROOTGrafTGaxis.h TGaxis_Clear"
               c_tgaxis_clear :: Ptr RawTGaxis -> CString -> IO ()

foreign import ccall interruptible "HROOTGrafTGaxis.h TGaxis_Draw"
               c_tgaxis_draw :: Ptr RawTGaxis -> CString -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_FindObject" c_tgaxis_findobject ::
               Ptr RawTGaxis -> CString -> IO (Ptr RawTObject)

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_GetName" c_tgaxis_getname ::
               Ptr RawTGaxis -> IO CString

foreign import ccall interruptible "HROOTGrafTGaxis.h TGaxis_IsA"
               c_tgaxis_isa :: Ptr RawTGaxis -> IO (Ptr RawTClass)

foreign import ccall interruptible "HROOTGrafTGaxis.h TGaxis_Paint"
               c_tgaxis_paint :: Ptr RawTGaxis -> CString -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_printObj" c_tgaxis_printobj ::
               Ptr RawTGaxis -> CString -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SaveAs" c_tgaxis_saveas ::
               Ptr RawTGaxis -> CString -> CString -> IO ()

foreign import ccall interruptible "HROOTGrafTGaxis.h TGaxis_Write"
               c_tgaxis_write ::
               Ptr RawTGaxis -> CString -> CInt -> CInt -> IO CInt

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_Write_" c_tgaxis_write_ ::
               Ptr RawTGaxis -> IO CInt

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_GetLineColor" c_tgaxis_getlinecolor ::
               Ptr RawTGaxis -> IO CShort

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_GetLineStyle" c_tgaxis_getlinestyle ::
               Ptr RawTGaxis -> IO CShort

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_GetLineWidth" c_tgaxis_getlinewidth ::
               Ptr RawTGaxis -> IO CShort

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_ResetAttLine" c_tgaxis_resetattline ::
               Ptr RawTGaxis -> CString -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetLineAttributes"
               c_tgaxis_setlineattributes :: Ptr RawTGaxis -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetLineColor" c_tgaxis_setlinecolor ::
               Ptr RawTGaxis -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetLineStyle" c_tgaxis_setlinestyle ::
               Ptr RawTGaxis -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_SetLineWidth" c_tgaxis_setlinewidth ::
               Ptr RawTGaxis -> CShort -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_delete" c_tgaxis_delete ::
               Ptr RawTGaxis -> IO ()

foreign import ccall interruptible
               "HROOTGrafTGaxis.h TGaxis_newTGaxis" c_tgaxis_newtgaxis ::
               CDouble ->
                 CDouble ->
                   CDouble ->
                     CDouble ->
                       CDouble ->
                         CDouble -> CInt -> CString -> CDouble -> IO (Ptr RawTGaxis)