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

-- module HROOT.Class.FFI where

module HROOT.Core.TAttText.FFI where


import Foreign.C            
import Foreign.Ptr

-- import HROOT.Class.Interface

-- #include ""

import HROOT.Core.TAttText.RawType



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

foreign import ccall "HROOTCoreTAttText.h TAttText_delete" c_tatttext_delete 
  :: (Ptr RawTAttText) -> IO ()

foreign import ccall "HROOTCoreTAttText.h TAttText_newTAttText" c_tatttext_newtatttext 
  :: CInt -> CDouble -> CInt -> CInt -> CDouble -> IO (Ptr RawTAttText)

foreign import ccall "HROOTCoreTAttText.h TAttText_GetTextAlign" c_tatttext_gettextalign 
  :: (Ptr RawTAttText) -> IO CInt

foreign import ccall "HROOTCoreTAttText.h TAttText_GetTextAngle" c_tatttext_gettextangle 
  :: (Ptr RawTAttText) -> IO CDouble

foreign import ccall "HROOTCoreTAttText.h TAttText_GetTextColor" c_tatttext_gettextcolor 
  :: (Ptr RawTAttText) -> IO CInt

foreign import ccall "HROOTCoreTAttText.h TAttText_GetTextFont" c_tatttext_gettextfont 
  :: (Ptr RawTAttText) -> IO CInt

foreign import ccall "HROOTCoreTAttText.h TAttText_GetTextSize" c_tatttext_gettextsize 
  :: (Ptr RawTAttText) -> IO CDouble

foreign import ccall "HROOTCoreTAttText.h TAttText_ResetAttText" c_tatttext_resetatttext 
  :: (Ptr RawTAttText) -> CString -> IO ()

foreign import ccall "HROOTCoreTAttText.h TAttText_SetTextAttributes" c_tatttext_settextattributes 
  :: (Ptr RawTAttText) -> IO ()

foreign import ccall "HROOTCoreTAttText.h TAttText_SetTextAlign" c_tatttext_settextalign 
  :: (Ptr RawTAttText) -> CInt -> IO ()

foreign import ccall "HROOTCoreTAttText.h TAttText_SetTextAngle" c_tatttext_settextangle 
  :: (Ptr RawTAttText) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttText.h TAttText_SetTextColor" c_tatttext_settextcolor 
  :: (Ptr RawTAttText) -> CInt -> IO ()

foreign import ccall "HROOTCoreTAttText.h TAttText_SetTextFont" c_tatttext_settextfont 
  :: (Ptr RawTAttText) -> CInt -> IO ()

foreign import ccall "HROOTCoreTAttText.h TAttText_SetTextSize" c_tatttext_settextsize 
  :: (Ptr RawTAttText) -> CDouble -> IO ()

foreign import ccall "HROOTCoreTAttText.h TAttText_SetTextSizePixels" c_tatttext_settextsizepixels 
  :: (Ptr RawTAttText) -> CInt -> IO ()