module HGamer3D.Bindings.Ogre.ClassRoot where
import Foreign
import Foreign.Ptr
import Foreign.C
import HGamer3D.Data.HG3DClass
import HGamer3D.Data.Vector
import HGamer3D.Data.Colour
import HGamer3D.Data.Angle
import HGamer3D.Bindings.Ogre.Utils
import HGamer3D.Bindings.Ogre.ClassPtr
import HGamer3D.Bindings.Ogre.StructHG3DClass
import HGamer3D.Bindings.Ogre.StructColour
new :: String -> String -> String -> IO (HG3DClass)
new a1 a2 a3 =
  withCString a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  alloca $ \a4' -> 
  new'_ a1' a2' a3' a4' >>= \res ->
  peek  a4'>>= \a4'' -> 
  return (a4'')
delete :: HG3DClass -> IO ()
delete a1 =
  withHG3DClass a1 $ \a1' -> 
  delete'_ a1' >>= \res ->
  return ()
saveConfig :: HG3DClass -> IO ()
saveConfig a1 =
  withHG3DClass a1 $ \a1' -> 
  saveConfig'_ a1' >>= \res ->
  return ()
restoreConfig :: HG3DClass -> IO (Bool)
restoreConfig a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  restoreConfig'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
showConfigDialog :: HG3DClass -> IO (Bool)
showConfigDialog a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  showConfigDialog'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
addRenderSystem :: HG3DClass -> HG3DClass -> IO ()
addRenderSystem a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  addRenderSystem'_ a1' a2' >>= \res ->
  return ()
getRenderSystemByName :: HG3DClass -> String -> IO (HG3DClass)
getRenderSystemByName a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  getRenderSystemByName'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
setRenderSystem :: HG3DClass -> HG3DClass -> IO ()
setRenderSystem a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setRenderSystem'_ a1' a2' >>= \res ->
  return ()
getRenderSystem :: HG3DClass -> IO (HG3DClass)
getRenderSystem a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRenderSystem'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
initialise :: HG3DClass -> Bool -> String -> String -> IO (HG3DClass)
initialise a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  withCString a3 $ \a3' -> 
  withCString a4 $ \a4' -> 
  alloca $ \a5' -> 
  initialise'_ a1' a2' a3' a4' a5' >>= \res ->
  peek  a5'>>= \a5'' -> 
  return (a5'')
isInitialised :: HG3DClass -> IO (Bool)
isInitialised a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isInitialised'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
getRemoveRenderQueueStructuresOnClear :: HG3DClass -> IO (Bool)
getRemoveRenderQueueStructuresOnClear a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRemoveRenderQueueStructuresOnClear'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
setRemoveRenderQueueStructuresOnClear :: HG3DClass -> Bool -> IO ()
setRemoveRenderQueueStructuresOnClear a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setRemoveRenderQueueStructuresOnClear'_ a1' a2' >>= \res ->
  return ()
addSceneManagerFactory :: HG3DClass -> HG3DClass -> IO ()
addSceneManagerFactory a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  addSceneManagerFactory'_ a1' a2' >>= \res ->
  return ()
removeSceneManagerFactory :: HG3DClass -> HG3DClass -> IO ()
removeSceneManagerFactory a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  removeSceneManagerFactory'_ a1' a2' >>= \res ->
  return ()
createSceneManager :: HG3DClass -> String -> String -> IO (HG3DClass)
createSceneManager a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  alloca $ \a4' -> 
  createSceneManager'_ a1' a2' a3' a4' >>= \res ->
  peek  a4'>>= \a4'' -> 
  return (a4'')
destroySceneManager :: HG3DClass -> HG3DClass -> IO ()
destroySceneManager a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  destroySceneManager'_ a1' a2' >>= \res ->
  return ()
getSceneManager :: HG3DClass -> String -> IO (HG3DClass)
getSceneManager a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  getSceneManager'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
hasSceneManager :: HG3DClass -> String -> IO (Bool)
hasSceneManager a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  hasSceneManager'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
getTextureManager :: HG3DClass -> IO (HG3DClass)
getTextureManager a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getTextureManager'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
getMeshManager :: HG3DClass -> IO (HG3DClass)
getMeshManager a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getMeshManager'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
getErrorDescription :: HG3DClass -> Int -> IO (String)
getErrorDescription a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloc64k $ \a3' -> 
  getErrorDescription'_ a1' a2' a3' >>= \res ->
  peekCString  a3'>>= \a3'' -> 
  return (a3'')
queueEndRendering :: HG3DClass -> IO ()
queueEndRendering a1 =
  withHG3DClass a1 $ \a1' -> 
  queueEndRendering'_ a1' >>= \res ->
  return ()
startRendering :: HG3DClass -> IO ()
startRendering a1 =
  withHG3DClass a1 $ \a1' -> 
  startRendering'_ a1' >>= \res ->
  return ()
renderOneFrame :: HG3DClass -> IO (Bool)
renderOneFrame a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  renderOneFrame'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
renderOneFrame2 :: HG3DClass -> Float -> IO (Bool)
renderOneFrame2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  alloca $ \a3' -> 
  renderOneFrame2'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
shutdown :: HG3DClass -> IO ()
shutdown a1 =
  withHG3DClass a1 $ \a1' -> 
  shutdown'_ a1' >>= \res ->
  return ()
addResourceLocation :: HG3DClass -> String -> String -> String -> Bool -> IO ()
addResourceLocation a1 a2 a3 a4 a5 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  withCString a4 $ \a4' -> 
  let {a5' = fromBool a5} in 
  addResourceLocation'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
removeResourceLocation :: HG3DClass -> String -> String -> IO ()
removeResourceLocation a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  removeResourceLocation'_ a1' a2' a3' >>= \res ->
  return ()
convertColourValue :: HG3DClass -> Colour -> IO (Int)
convertColourValue a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withColour a2 $ \a2' -> 
  alloca $ \a3' -> 
  convertColourValue'_ a1' a2' a3' >>= \res ->
  peekIntConv  a3'>>= \a3'' -> 
  return (a3'')
getAutoCreatedWindow :: HG3DClass -> IO (HG3DClass)
getAutoCreatedWindow a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getAutoCreatedWindow'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
detachRenderTarget :: HG3DClass -> HG3DClass -> IO (HG3DClass)
detachRenderTarget a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  alloca $ \a3' -> 
  detachRenderTarget'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
detachRenderTarget2 :: HG3DClass -> String -> IO (HG3DClass)
detachRenderTarget2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  detachRenderTarget2'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
destroyRenderTarget :: HG3DClass -> HG3DClass -> IO ()
destroyRenderTarget a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  destroyRenderTarget'_ a1' a2' >>= \res ->
  return ()
destroyRenderTarget2 :: HG3DClass -> String -> IO ()
destroyRenderTarget2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  destroyRenderTarget2'_ a1' a2' >>= \res ->
  return ()
getRenderTarget :: HG3DClass -> String -> IO (HG3DClass)
getRenderTarget a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  getRenderTarget'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
loadPlugin :: HG3DClass -> String -> IO ()
loadPlugin a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  loadPlugin'_ a1' a2' >>= \res ->
  return ()
unloadPlugin :: HG3DClass -> String -> IO ()
unloadPlugin a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  unloadPlugin'_ a1' a2' >>= \res ->
  return ()
destroyRenderQueueInvocationSequence :: HG3DClass -> String -> IO ()
destroyRenderQueueInvocationSequence a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  destroyRenderQueueInvocationSequence'_ a1' a2' >>= \res ->
  return ()
destroyAllRenderQueueInvocationSequences :: HG3DClass -> IO ()
destroyAllRenderQueueInvocationSequences a1 =
  withHG3DClass a1 $ \a1' -> 
  destroyAllRenderQueueInvocationSequences'_ a1' >>= \res ->
  return ()
clearEventTimes :: HG3DClass -> IO ()
clearEventTimes a1 =
  withHG3DClass a1 $ \a1' -> 
  clearEventTimes'_ a1' >>= \res ->
  return ()
setFrameSmoothingPeriod :: HG3DClass -> Float -> IO ()
setFrameSmoothingPeriod a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setFrameSmoothingPeriod'_ a1' a2' >>= \res ->
  return ()
getFrameSmoothingPeriod :: HG3DClass -> IO (Float)
getFrameSmoothingPeriod a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getFrameSmoothingPeriod'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
addMovableObjectFactory :: HG3DClass -> HG3DClass -> Bool -> IO ()
addMovableObjectFactory a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  let {a3' = fromBool a3} in 
  addMovableObjectFactory'_ a1' a2' a3' >>= \res ->
  return ()
removeMovableObjectFactory :: HG3DClass -> HG3DClass -> IO ()
removeMovableObjectFactory a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  removeMovableObjectFactory'_ a1' a2' >>= \res ->
  return ()
hasMovableObjectFactory :: HG3DClass -> String -> IO (Bool)
hasMovableObjectFactory a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  hasMovableObjectFactory'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
getMovableObjectFactory :: HG3DClass -> String -> IO (HG3DClass)
getMovableObjectFactory a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  getMovableObjectFactory'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
getDisplayMonitorCount :: HG3DClass -> IO (Int)
getDisplayMonitorCount a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDisplayMonitorCount'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
setBlendIndicesGpuRedundant :: HG3DClass -> Bool -> IO ()
setBlendIndicesGpuRedundant a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setBlendIndicesGpuRedundant'_ a1' a2' >>= \res ->
  return ()
isBlendIndicesGpuRedundant :: HG3DClass -> IO (Bool)
isBlendIndicesGpuRedundant a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isBlendIndicesGpuRedundant'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
setBlendWeightsGpuRedundant :: HG3DClass -> Bool -> IO ()
setBlendWeightsGpuRedundant a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setBlendWeightsGpuRedundant'_ a1' a2' >>= \res ->
  return ()
isBlendWeightsGpuRedundant :: HG3DClass -> IO (Bool)
isBlendWeightsGpuRedundant a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isBlendWeightsGpuRedundant'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
setDefaultMinPixelSize :: HG3DClass -> Float -> IO ()
setDefaultMinPixelSize a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setDefaultMinPixelSize'_ a1' a2' >>= \res ->
  return ()
getDefaultMinPixelSize :: HG3DClass -> IO (Float)
getDefaultMinPixelSize a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDefaultMinPixelSize'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
getSingleton :: IO (HG3DClass)
getSingleton =
  alloca $ \a1' -> 
  getSingleton'_ a1' >>= \res ->
  peek  a1'>>= \a1'' -> 
  return (a1'')
getSingletonPtr :: IO (HG3DClass)
getSingletonPtr =
  alloca $ \a1' -> 
  getSingletonPtr'_ a1' >>= \res ->
  peek  a1'>>= \a1'' -> 
  return (a1'')
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_construct"
  new'_ :: ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ())))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_destruct"
  delete'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_saveConfig"
  saveConfig'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_restoreConfig"
  restoreConfig'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_showConfigDialog"
  showConfigDialog'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_addRenderSystem"
  addRenderSystem'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getRenderSystemByName"
  getRenderSystemByName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_setRenderSystem"
  setRenderSystem'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getRenderSystem"
  getRenderSystem'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_initialise"
  initialise'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CChar) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_isInitialised"
  isInitialised'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getRemoveRenderQueueStructuresOnClear"
  getRemoveRenderQueueStructuresOnClear'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_setRemoveRenderQueueStructuresOnClear"
  setRemoveRenderQueueStructuresOnClear'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_addSceneManagerFactory"
  addSceneManagerFactory'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_removeSceneManagerFactory"
  removeSceneManagerFactory'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_createSceneManager"
  createSceneManager'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ())))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_destroySceneManager"
  destroySceneManager'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getSceneManager"
  getSceneManager'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_hasSceneManager"
  hasSceneManager'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getTextureManager"
  getTextureManager'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getMeshManager"
  getMeshManager'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getErrorDescription"
  getErrorDescription'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CChar) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_queueEndRendering"
  queueEndRendering'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_startRendering"
  startRendering'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_renderOneFrame"
  renderOneFrame'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_renderOneFrame2"
  renderOneFrame2'_ :: ((HG3DClassPtr) -> (CFloat -> ((Ptr CInt) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_shutdown"
  shutdown'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_addResourceLocation"
  addResourceLocation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> (CInt -> (IO ()))))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_removeResourceLocation"
  removeResourceLocation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_convertColourValue"
  convertColourValue'_ :: ((HG3DClassPtr) -> ((ColourPtr) -> ((Ptr CUInt) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getAutoCreatedWindow"
  getAutoCreatedWindow'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_detachRenderTarget"
  detachRenderTarget'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_detachRenderTarget2"
  detachRenderTarget2'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_destroyRenderTarget"
  destroyRenderTarget'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_destroyRenderTarget2"
  destroyRenderTarget2'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getRenderTarget"
  getRenderTarget'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_loadPlugin"
  loadPlugin'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_unloadPlugin"
  unloadPlugin'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_destroyRenderQueueInvocationSequence"
  destroyRenderQueueInvocationSequence'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_destroyAllRenderQueueInvocationSequences"
  destroyAllRenderQueueInvocationSequences'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_clearEventTimes"
  clearEventTimes'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_setFrameSmoothingPeriod"
  setFrameSmoothingPeriod'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getFrameSmoothingPeriod"
  getFrameSmoothingPeriod'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_addMovableObjectFactory"
  addMovableObjectFactory'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CInt -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_removeMovableObjectFactory"
  removeMovableObjectFactory'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_hasMovableObjectFactory"
  hasMovableObjectFactory'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getMovableObjectFactory"
  getMovableObjectFactory'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getDisplayMonitorCount"
  getDisplayMonitorCount'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_setBlendIndicesGpuRedundant"
  setBlendIndicesGpuRedundant'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_isBlendIndicesGpuRedundant"
  isBlendIndicesGpuRedundant'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_setBlendWeightsGpuRedundant"
  setBlendWeightsGpuRedundant'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_isBlendWeightsGpuRedundant"
  isBlendWeightsGpuRedundant'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_setDefaultMinPixelSize"
  setDefaultMinPixelSize'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getDefaultMinPixelSize"
  getDefaultMinPixelSize'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getSingleton"
  getSingleton'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRoot.chs.h ogre_rt_getSingletonPtr"
  getSingletonPtr'_ :: ((HG3DClassPtr) -> (IO ()))