-- GENERATED by C->Haskell Compiler, version 0.16.3 Crystal Seed, 24 Jan 2009 (Haskell)
-- Edit the ORIGNAL .chs file instead!


{-# LINE 1 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE TypeSynonymInstances #-}

-- This source file is part of HGamer3D
-- (A project to enable 3D game development in Haskell)
-- For the latest info, see http://www.althainz.de/HGamer3D.html
-- 

-- (c) 2011-2013 Peter Althainz
-- 
-- The files are part of HGamer3D (www.hgamer3d.org)
-- 
-- Licensed under the Apache License, Version 2.0 (the "License");
-- you may not use this file except in compliance with the License.
-- You may obtain a copy of the License at
-- 
--     http://www.apache.org/licenses/LICENSE-2.0
-- 
-- Unless required by applicable law or agreed to in writing, software
-- distributed under the License is distributed on an "AS IS" BASIS,
-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-- See the License for the specific language governing permissions and
-- limitations under the License.
-- 


-- ClassRenderTarget.chs

-- 

module HGamer3D.Bindings.Ogre.ClassRenderTarget 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
{-# LINE 42 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}
import HGamer3D.Bindings.Ogre.ClassPtr
{-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}
import HGamer3D.Bindings.Ogre.StructHG3DClass
{-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function ~RenderTarget -}
delete :: HG3DClass -> IO ()
delete a1 =
  withHG3DClass a1 $ \a1' -> 
  delete'_ a1' >>= \res ->
  return ()
{-# LINE 49 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getName -}
getName :: HG3DClass -> IO (String)
getName a1 =
  withHG3DClass a1 $ \a1' -> 
  alloc64k $ \a2' -> 
  getName'_ a1' a2' >>= \res ->
  peekCString  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 54 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getMetrics -}
getMetrics :: HG3DClass -> IO (Int, Int, Int)
getMetrics a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  getMetrics'_ a1' a2' a3' a4' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  peekIntConv  a3'>>= \a3'' -> 
  peekIntConv  a4'>>= \a4'' -> 
  return (a2'', a3'', a4'')
{-# LINE 61 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getWidth -}
getWidth :: HG3DClass -> IO (Int)
getWidth a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getWidth'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 66 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getHeight -}
getHeight :: HG3DClass -> IO (Int)
getHeight a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getHeight'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 71 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getColourDepth -}
getColourDepth :: HG3DClass -> IO (Int)
getColourDepth a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getColourDepth'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 76 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function setDepthBufferPool -}
setDepthBufferPool :: HG3DClass -> Int -> IO ()
setDepthBufferPool a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  setDepthBufferPool'_ a1' a2' >>= \res ->
  return ()
{-# LINE 81 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getDepthBufferPool -}
getDepthBufferPool :: HG3DClass -> IO (Int)
getDepthBufferPool a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDepthBufferPool'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 86 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function detachDepthBuffer -}
detachDepthBuffer :: HG3DClass -> IO ()
detachDepthBuffer a1 =
  withHG3DClass a1 $ \a1' -> 
  detachDepthBuffer'_ a1' >>= \res ->
  return ()
{-# LINE 90 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function update -}
update :: HG3DClass -> Bool -> IO ()
update a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  update'_ a1' a2' >>= \res ->
  return ()
{-# LINE 95 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function swapBuffers -}
swapBuffers :: HG3DClass -> Bool -> IO ()
swapBuffers a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  swapBuffers'_ a1' a2' >>= \res ->
  return ()
{-# LINE 100 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function addViewport -}
addViewport :: HG3DClass -> HG3DClass -> Int -> Float -> Float -> Float -> Float -> IO (HG3DClass)
addViewport a1 a2 a3 a4 a5 a6 a7 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  let {a6' = realToFrac a6} in 
  let {a7' = realToFrac a7} in 
  alloca $ \a8' -> 
  addViewport'_ a1' a2' a3' a4' a5' a6' a7' a8' >>= \res ->
  peek  a8'>>= \a8'' -> 
  return (a8'')
{-# LINE 111 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getNumViewports -}
getNumViewports :: HG3DClass -> IO (Int)
getNumViewports a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getNumViewports'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 116 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getViewport -}
getViewport :: HG3DClass -> Int -> IO (HG3DClass)
getViewport a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getViewport'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 122 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getViewportByZOrder -}
getViewportByZOrder :: HG3DClass -> Int -> IO (HG3DClass)
getViewportByZOrder a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getViewportByZOrder'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 128 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function hasViewportWithZOrder -}
hasViewportWithZOrder :: HG3DClass -> Int -> IO (Bool)
hasViewportWithZOrder a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  hasViewportWithZOrder'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 134 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function removeViewport -}
removeViewport :: HG3DClass -> Int -> IO ()
removeViewport a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  removeViewport'_ a1' a2' >>= \res ->
  return ()
{-# LINE 139 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function removeAllViewports -}
removeAllViewports :: HG3DClass -> IO ()
removeAllViewports a1 =
  withHG3DClass a1 $ \a1' -> 
  removeAllViewports'_ a1' >>= \res ->
  return ()
{-# LINE 143 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getStatistics -}
getStatistics :: HG3DClass -> IO (Float, Float, Float, Float)
getStatistics a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  alloca $ \a5' -> 
  getStatistics'_ a1' a2' a3' a4' a5' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  peekFloatConv  a3'>>= \a3'' -> 
  peekFloatConv  a4'>>= \a4'' -> 
  peekFloatConv  a5'>>= \a5'' -> 
  return (a2'', a3'', a4'', a5'')
{-# LINE 151 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getLastFPS -}
getLastFPS :: HG3DClass -> IO (Float)
getLastFPS a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getLastFPS'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 156 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getAverageFPS -}
getAverageFPS :: HG3DClass -> IO (Float)
getAverageFPS a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getAverageFPS'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 161 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getBestFPS -}
getBestFPS :: HG3DClass -> IO (Float)
getBestFPS a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getBestFPS'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 166 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getWorstFPS -}
getWorstFPS :: HG3DClass -> IO (Float)
getWorstFPS a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getWorstFPS'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 171 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getBestFrameTime -}
getBestFrameTime :: HG3DClass -> IO (Float)
getBestFrameTime a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getBestFrameTime'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 176 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getWorstFrameTime -}
getWorstFrameTime :: HG3DClass -> IO (Float)
getWorstFrameTime a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getWorstFrameTime'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 181 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function resetStatistics -}
resetStatistics :: HG3DClass -> IO ()
resetStatistics a1 =
  withHG3DClass a1 $ \a1' -> 
  resetStatistics'_ a1' >>= \res ->
  return ()
{-# LINE 185 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function removeAllListeners -}
removeAllListeners :: HG3DClass -> IO ()
removeAllListeners a1 =
  withHG3DClass a1 $ \a1' -> 
  removeAllListeners'_ a1' >>= \res ->
  return ()
{-# LINE 189 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function isActive -}
isActive :: HG3DClass -> IO (Bool)
isActive a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isActive'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 194 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function setActive -}
setActive :: HG3DClass -> Bool -> IO ()
setActive a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setActive'_ a1' a2' >>= \res ->
  return ()
{-# LINE 199 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function setAutoUpdated -}
setAutoUpdated :: HG3DClass -> Bool -> IO ()
setAutoUpdated a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setAutoUpdated'_ a1' a2' >>= \res ->
  return ()
{-# LINE 204 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function isAutoUpdated -}
isAutoUpdated :: HG3DClass -> IO (Bool)
isAutoUpdated a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isAutoUpdated'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 209 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function writeContentsToFile -}
writeContentsToFile :: HG3DClass -> String -> IO ()
writeContentsToFile a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  writeContentsToFile'_ a1' a2' >>= \res ->
  return ()
{-# LINE 214 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function writeContentsToTimestampedFile -}
writeContentsToTimestampedFile :: HG3DClass -> String -> String -> IO (String)
writeContentsToTimestampedFile a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  alloc64k $ \a4' -> 
  writeContentsToTimestampedFile'_ a1' a2' a3' a4' >>= \res ->
  peekCString  a4'>>= \a4'' -> 
  return (a4'')
{-# LINE 221 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function requiresTextureFlipping -}
requiresTextureFlipping :: HG3DClass -> IO (Bool)
requiresTextureFlipping a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  requiresTextureFlipping'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 226 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getTriangleCount -}
getTriangleCount :: HG3DClass -> IO (Int)
getTriangleCount a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getTriangleCount'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 231 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getBatchCount -}
getBatchCount :: HG3DClass -> IO (Int)
getBatchCount a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getBatchCount'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 236 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function isPrimary -}
isPrimary :: HG3DClass -> IO (Bool)
isPrimary a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isPrimary'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 241 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function isHardwareGammaEnabled -}
isHardwareGammaEnabled :: HG3DClass -> IO (Bool)
isHardwareGammaEnabled a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isHardwareGammaEnabled'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 246 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getFSAA -}
getFSAA :: HG3DClass -> IO (Int)
getFSAA a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getFSAA'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 251 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

{- function getFSAAHint -}
getFSAAHint :: HG3DClass -> IO (String)
getFSAAHint a1 =
  withHG3DClass a1 $ \a1' -> 
  alloc64k $ \a2' -> 
  getFSAAHint'_ a1' a2' >>= \res ->
  peekCString  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 256 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}


foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_destruct"
  delete'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getName"
  getName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getMetrics"
  getMetrics'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> ((Ptr CUInt) -> ((Ptr CUInt) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getWidth"
  getWidth'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getHeight"
  getHeight'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getColourDepth"
  getColourDepth'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_setDepthBufferPool"
  setDepthBufferPool'_ :: ((HG3DClassPtr) -> (CUShort -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getDepthBufferPool"
  getDepthBufferPool'_ :: ((HG3DClassPtr) -> ((Ptr CUShort) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_detachDepthBuffer"
  detachDepthBuffer'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_update"
  update'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_swapBuffers"
  swapBuffers'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_addViewport"
  addViewport'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (CInt -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> ((HG3DClassPtr) -> (IO ())))))))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getNumViewports"
  getNumViewports'_ :: ((HG3DClassPtr) -> ((Ptr CUShort) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getViewport"
  getViewport'_ :: ((HG3DClassPtr) -> (CUShort -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getViewportByZOrder"
  getViewportByZOrder'_ :: ((HG3DClassPtr) -> (CInt -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_hasViewportWithZOrder"
  hasViewportWithZOrder'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_removeViewport"
  removeViewport'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_removeAllViewports"
  removeAllViewports'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getStatistics"
  getStatistics'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getLastFPS"
  getLastFPS'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getAverageFPS"
  getAverageFPS'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getBestFPS"
  getBestFPS'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getWorstFPS"
  getWorstFPS'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getBestFrameTime"
  getBestFrameTime'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getWorstFrameTime"
  getWorstFrameTime'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_resetStatistics"
  resetStatistics'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_removeAllListeners"
  removeAllListeners'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_isActive"
  isActive'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_setActive"
  setActive'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_setAutoUpdated"
  setAutoUpdated'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_isAutoUpdated"
  isAutoUpdated'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_writeContentsToFile"
  writeContentsToFile'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_writeContentsToTimestampedFile"
  writeContentsToTimestampedFile'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_requiresTextureFlipping"
  requiresTextureFlipping'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getTriangleCount"
  getTriangleCount'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getBatchCount"
  getBatchCount'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_isPrimary"
  isPrimary'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_isHardwareGammaEnabled"
  isHardwareGammaEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getFSAA"
  getFSAA'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs.h ogre_rtgt_getFSAAHint"
  getFSAAHint'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))