-- 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, 2012 Peter Althainz
-- 
-- 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 40 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}
import HGamer3D.Bindings.Ogre.ClassPtr
{-# LINE 41 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}
import HGamer3D.Bindings.Ogre.StructHG3DClass
{-# LINE 42 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | 
delete :: HG3DClass  -- ^ classpointer - pointer of Class instance which is going to be deleted.
  ->  IO ()
 -- ^ 
delete a1 =
  withHG3DClass a1 $ \a1' -> 
  delete'_ a1' >>= \res ->
  return ()
{-# LINE 47 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Retrieve target's name. 
getName :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (String)
 -- ^ 
getName a1 =
  withHG3DClass a1 $ \a1' -> 
  alloc64k $ \a2' -> 
  getName'_ a1' a2' >>= \res ->
  peekCString  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 52 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Retrieve information about the render target. 
getMetrics :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int, Int, Int)
 -- ^ width
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 59 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | 
getWidth :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getWidth a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getWidth'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 64 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | 
getHeight :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getHeight a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getHeight'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 69 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | 
getColourDepth :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getColourDepth a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getColourDepth'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 74 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Tells the target to update it's contents. If OGRE is not running in an automatic rendering loop (started using Root::startRenderingThis allows OGRE to be used in multi-windowed utilities and for contents to be refreshed only when required, rather than constantly as with the automatic rendering loop. 
update :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ swapBuffers - For targets that support double-buffering, if set to true, the target will immediately swap it's buffers after update. Otherwise, the buffers are not swapped, and you have to call swapBuffers yourself sometime later. You might want to do this on some rendersystems which pause for queued rendering commands to complete before accepting swap buffers calls - so you could do other CPU tasks whilst the queued commands complete. Or, you might do this if you want custom control over your windows, such as for externally created windows. 
  ->  IO ()
 -- ^ 
update a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  update'_ a1' a2' >>= \res ->
  return ()
{-# LINE 79 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Swaps the frame buffers to display the next frame. For targets that are double-buffered so that no 'in-progress' versions of the scene are displayed during rendering. Once rendering has completed (to an off-screen version of the window) the buffers are swapped to display the new frame.
swapBuffers :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ waitForVSync - If true, the system waits for the next vertical blank period (when the CRT beam turns off as it travels from bottom-right to top-left at the end of the pass) before flipping. If false, flipping occurs no matter what the beam position. Waiting for a vertical blank can be slower (and limits the framerate to the monitor refresh rate) but results in a steadier image with no 'tearing' (a flicker resulting from flipping buffers when the beam is in the progress of drawing the last frame). 
  ->  IO ()
 -- ^ 
swapBuffers a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  swapBuffers'_ a1' a2' >>= \res ->
  return ()
{-# LINE 84 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Adds a viewport to the rendering target. A viewport is the rectangle into which rendering output is sent. This method adds a viewport to the render target, rendering from the supplied camera. The rest of the parameters are only required if you wish to add more than one viewport to a single rendering target. Note that size information passed to this method is passed as a parametric, i.e. it is relative rather than absolute. This is to allow viewports to automatically resize along with the target. 
addViewport :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  HG3DClass  -- ^ cam - The camera from which the viewport contents will be rendered (mandatory) 
  ->  Int  -- ^ ZOrder - The relative order of the viewport with others on the target (allows overlapping viewports i.e. picture-in-picture). Higher ZOrders are on top of lower ones. The actual number is irrelevant, only the relative ZOrder matters (you can leave gaps in the numbering) 
  ->  Float  -- ^ left - The relative position of the left of the viewport on the target, as a value between 0 and 1. 
  ->  Float  -- ^ top - The relative position of the top of the viewport on the target, as a value between 0 and 1. 
  ->  Float  -- ^ width - The relative width of the viewport on the target, as a value between 0 and 1. 
  ->  Float  -- ^ height - The relative height of the viewport on the target, as a value between 0 and 1. 
  ->  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 95 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Returns the number of viewports attached to this target. 
getNumViewports :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getNumViewports a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getNumViewports'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 100 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Retrieves a pointer to the viewport with the given index. 
getViewport :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ index
  ->  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 106 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Removes a viewport at a given ZOrder. 
removeViewport :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ ZOrder
  ->  IO ()
 -- ^ 
removeViewport a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  removeViewport'_ a1' a2' >>= \res ->
  return ()
{-# LINE 111 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Removes all viewports on this target. 
removeAllViewports :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
removeAllViewports a1 =
  withHG3DClass a1 $ \a1' -> 
  removeAllViewports'_ a1' >>= \res ->
  return ()
{-# LINE 115 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Retieves details of current rendering performance. If the user application wishes to do it's own performance display, or use performance for some other means, this method allows it to retrieve the statistics. 
getStatistics :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float, Float, Float, Float)
 -- ^ lastFPS - Pointer to a float to receive the number of frames per second (FPS) based on the last frame rendered. 
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 123 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Individual stats access - gets the number of frames per second (FPS) based on the last frame rendered. 
getLastFPS :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ 
getLastFPS a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getLastFPS'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 128 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Individual stats access - gets the average frames per second (FPS) since call to Root::startRendering
getAverageFPS :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ 
getAverageFPS a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getAverageFPS'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 133 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Individual stats access - gets the best frames per second (FPS) since call to Root::startRendering
getBestFPS :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ 
getBestFPS a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getBestFPS'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 138 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Individual stats access - gets the worst frames per second (FPS) since call to Root::startRendering
getWorstFPS :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ 
getWorstFPS a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getWorstFPS'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 143 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Individual stats access - gets the best frame time 
getBestFrameTime :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ 
getBestFrameTime a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getBestFrameTime'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 148 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Individual stats access - gets the worst frame time 
getWorstFrameTime :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ 
getWorstFrameTime a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getWorstFrameTime'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 153 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Resets saved frame-rate statistices. 
resetStatistics :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
resetStatistics a1 =
  withHG3DClass a1 $ \a1' -> 
  resetStatistics'_ a1' >>= \res ->
  return ()
{-# LINE 157 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Removes all listeners from this instance. 
removeAllListeners :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
removeAllListeners a1 =
  withHG3DClass a1 $ \a1' -> 
  removeAllListeners'_ a1' >>= \res ->
  return ()
{-# LINE 161 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Used to retrieve or set the active state of the render target. 
isActive :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
isActive a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isActive'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 166 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Used to set the active state of the render target. 
setActive :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ state
  ->  IO ()
 -- ^ 
setActive a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setActive'_ a1' a2' >>= \res ->
  return ()
{-# LINE 171 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Sets whether this target should be automatically updated if OgreRoot::_updateAllRenderTargetsBy default, if you use OgreRoot::startRenderingRoot::_updateAllRenderTargets
setAutoUpdated :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ autoupdate - If true, the render target is updated during the automatic render loop or when Root::_updateAllRenderTargets is called. If false, the target is only updated when its update() method is called explicitly. 
  ->  IO ()
 -- ^ 
setAutoUpdated a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setAutoUpdated'_ a1' a2' >>= \res ->
  return ()
{-# LINE 176 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Gets whether this target is automatically updated if OgreRoot::_updateAllRenderTargets
isAutoUpdated :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
isAutoUpdated a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isAutoUpdated'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 181 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Writes the current contents of the render target to the named file. 
writeContentsToFile :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ filename
  ->  IO ()
 -- ^ 
writeContentsToFile a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  writeContentsToFile'_ a1' a2' >>= \res ->
  return ()
{-# LINE 186 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Writes the current contents of the render target to the (PREFIX)(time-stamp)(SUFFIX) file. 
writeContentsToTimestampedFile :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ filenamePrefix
  ->  String  -- ^ filenameSuffix
  ->  IO (String)
 -- ^ return value - the name of the file used.     
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 193 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | 
requiresTextureFlipping :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
requiresTextureFlipping a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  requiresTextureFlipping'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 198 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Gets the number of triangles rendered in the last update()
getTriangleCount :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getTriangleCount a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getTriangleCount'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 203 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Gets the number of batches rendered in the last update()
getBatchCount :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getBatchCount a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getBatchCount'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 208 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Indicates whether this target is the primary window. The primary window is special in that it is destroyed when ogre is shut down, and cannot be destroyed directly. This is the case because it holds the context for vertex, index buffers and textures. 
isPrimary :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
isPrimary a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isPrimary'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 213 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Indicates whether on rendering, linear colour space is converted to sRGB gamma colour space. This is the exact opposite conversion of what is indicated by Texture::isHardwareGammaEnabled, and can only be enabled on creation of the render target. For render windows, it's enabled through the 'gamma' creation misc parameter. For textures, it is enabled through the hwGamma parameter to the create call. 
isHardwareGammaEnabled :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
isHardwareGammaEnabled a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isHardwareGammaEnabled'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 218 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Indicates whether multisampling is performed on rendering and at what level. 
getFSAA :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getFSAA a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getFSAA'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 223 ".\\HGamer3D\\Bindings\\Ogre\\ClassRenderTarget.chs" #-}

-- | Gets the FSAA hint (Root::createRenderWindow
getFSAAHint :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (String)
 -- ^ 
getFSAAHint a1 =
  withHG3DClass a1 $ \a1' -> 
  alloc64k $ \a2' -> 
  getFSAAHint'_ a1' a2' >>= \res ->
  peekCString  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 228 ".\\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_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_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 ())))