-- 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\\ClassCamera.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.
-- 


-- ClassCamera.chs

-- 

module HGamer3D.Bindings.Ogre.ClassCamera 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\\ClassCamera.chs" #-}
import HGamer3D.Bindings.Ogre.ClassPtr
{-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}
import HGamer3D.Bindings.Ogre.StructHG3DClass
{-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}
import HGamer3D.Bindings.Ogre.StructVec3
{-# LINE 45 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}
import HGamer3D.Bindings.Ogre.StructRadians
{-# LINE 46 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}
import HGamer3D.Bindings.Ogre.StructQuaternion
{-# LINE 47 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}
import HGamer3D.Bindings.Ogre.EnumFrustumPlane
{-# LINE 48 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function Camera -}
new :: String -> HG3DClass -> IO (HG3DClass)
new a1 a2 =
  withCString a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  alloca $ \a3' -> 
  new'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 55 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

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

{- function getSceneManager -}
getSceneManager :: HG3DClass -> IO (HG3DClass)
getSceneManager a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSceneManager'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 64 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function setPosition -}
setPosition :: HG3DClass -> Float -> Float -> Float -> IO ()
setPosition a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  setPosition'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 71 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function setPosition2 -}
setPosition2 :: HG3DClass -> Vec3 -> IO ()
setPosition2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  setPosition2'_ a1' a2' >>= \res ->
  return ()
{-# LINE 76 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getPosition -}
getPosition :: HG3DClass -> IO (Vec3)
getPosition a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getPosition'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 81 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function move -}
move :: HG3DClass -> Vec3 -> IO ()
move a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  move'_ a1' a2' >>= \res ->
  return ()
{-# LINE 86 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function moveRelative -}
moveRelative :: HG3DClass -> Vec3 -> IO ()
moveRelative a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  moveRelative'_ a1' a2' >>= \res ->
  return ()
{-# LINE 91 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function setDirection -}
setDirection :: HG3DClass -> Float -> Float -> Float -> IO ()
setDirection a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  setDirection'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 98 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function setDirection2 -}
setDirection2 :: HG3DClass -> Vec3 -> IO ()
setDirection2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  setDirection2'_ a1' a2' >>= \res ->
  return ()
{-# LINE 103 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getDirection -}
getDirection :: HG3DClass -> IO (Vec3)
getDirection a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDirection'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 108 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getUp -}
getUp :: HG3DClass -> IO (Vec3)
getUp a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getUp'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 113 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getRight -}
getRight :: HG3DClass -> IO (Vec3)
getRight a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRight'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 118 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function lookAt -}
lookAt :: HG3DClass -> Vec3 -> IO ()
lookAt a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  lookAt'_ a1' a2' >>= \res ->
  return ()
{-# LINE 123 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function lookAt2 -}
lookAt2 :: HG3DClass -> Float -> Float -> Float -> IO ()
lookAt2 a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  lookAt2'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 130 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function roll -}
roll :: HG3DClass -> Radians -> IO ()
roll a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withRadians a2 $ \a2' -> 
  roll'_ a1' a2' >>= \res ->
  return ()
{-# LINE 135 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function yaw -}
yaw :: HG3DClass -> Radians -> IO ()
yaw a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withRadians a2 $ \a2' -> 
  yaw'_ a1' a2' >>= \res ->
  return ()
{-# LINE 140 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function pitch -}
pitch :: HG3DClass -> Radians -> IO ()
pitch a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withRadians a2 $ \a2' -> 
  pitch'_ a1' a2' >>= \res ->
  return ()
{-# LINE 145 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function rotate -}
rotate :: HG3DClass -> Vec3 -> Radians -> IO ()
rotate a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  withRadians a3 $ \a3' -> 
  rotate'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 151 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function rotate2 -}
rotate2 :: HG3DClass -> Quaternion -> IO ()
rotate2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withQuaternion a2 $ \a2' -> 
  rotate2'_ a1' a2' >>= \res ->
  return ()
{-# LINE 156 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function setFixedYawAxis -}
setFixedYawAxis :: HG3DClass -> Bool -> Vec3 -> IO ()
setFixedYawAxis a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  withVec3 a3 $ \a3' -> 
  setFixedYawAxis'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 162 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getOrientation -}
getOrientation :: HG3DClass -> IO (Quaternion)
getOrientation a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getOrientation'_ a1' a2' >>= \res ->
  peekQuaternion  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 167 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function setOrientation -}
setOrientation :: HG3DClass -> Quaternion -> IO ()
setOrientation a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withQuaternion a2 $ \a2' -> 
  setOrientation'_ a1' a2' >>= \res ->
  return ()
{-# LINE 172 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getDerivedOrientation -}
getDerivedOrientation :: HG3DClass -> IO (Quaternion)
getDerivedOrientation a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDerivedOrientation'_ a1' a2' >>= \res ->
  peekQuaternion  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 177 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getDerivedPosition -}
getDerivedPosition :: HG3DClass -> IO (Vec3)
getDerivedPosition a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDerivedPosition'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 182 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getDerivedDirection -}
getDerivedDirection :: HG3DClass -> IO (Vec3)
getDerivedDirection a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDerivedDirection'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 187 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getDerivedUp -}
getDerivedUp :: HG3DClass -> IO (Vec3)
getDerivedUp a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDerivedUp'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 192 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getDerivedRight -}
getDerivedRight :: HG3DClass -> IO (Vec3)
getDerivedRight a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDerivedRight'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 197 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getRealOrientation -}
getRealOrientation :: HG3DClass -> IO (Quaternion)
getRealOrientation a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRealOrientation'_ a1' a2' >>= \res ->
  peekQuaternion  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 202 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getRealPosition -}
getRealPosition :: HG3DClass -> IO (Vec3)
getRealPosition a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRealPosition'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 207 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getRealDirection -}
getRealDirection :: HG3DClass -> IO (Vec3)
getRealDirection a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRealDirection'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 212 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getRealUp -}
getRealUp :: HG3DClass -> IO (Vec3)
getRealUp a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRealUp'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 217 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getRealRight -}
getRealRight :: HG3DClass -> IO (Vec3)
getRealRight a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRealRight'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 222 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

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

{- function setLodBias -}
setLodBias :: HG3DClass -> Float -> IO ()
setLodBias a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setLodBias'_ a1' a2' >>= \res ->
  return ()
{-# LINE 232 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

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

{- function setLodCamera -}
setLodCamera :: HG3DClass -> HG3DClass -> IO ()
setLodCamera a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setLodCamera'_ a1' a2' >>= \res ->
  return ()
{-# LINE 242 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getLodCamera -}
getLodCamera :: HG3DClass -> IO (HG3DClass)
getLodCamera a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getLodCamera'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 247 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function setWindow -}
setWindow :: HG3DClass -> Float -> Float -> Float -> Float -> IO ()
setWindow a1 a2 a3 a4 a5 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  let {a5' = realToFrac a5} in 
  setWindow'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 255 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

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

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

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

{- function getAutoTrackTarget -}
getAutoTrackTarget :: HG3DClass -> IO (HG3DClass)
getAutoTrackTarget a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getAutoTrackTarget'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 274 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getAutoTrackOffset -}
getAutoTrackOffset :: HG3DClass -> IO (Vec3)
getAutoTrackOffset a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getAutoTrackOffset'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 279 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getViewport -}
getViewport :: HG3DClass -> IO (HG3DClass)
getViewport a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getViewport'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 284 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

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

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

{- function setCullingFrustum -}
setCullingFrustum :: HG3DClass -> HG3DClass -> IO ()
setCullingFrustum a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setCullingFrustum'_ a1' a2' >>= \res ->
  return ()
{-# LINE 299 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getCullingFrustum -}
getCullingFrustum :: HG3DClass -> IO (HG3DClass)
getCullingFrustum a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getCullingFrustum'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 304 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function isVisible3 -}
isVisible3 :: HG3DClass -> Vec3 -> IO (EnumFrustumPlane, Bool)
isVisible3 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  alloca $ \a3' -> 
  alloca $ \a4' -> 
  isVisible3'_ a1' a2' a3' a4' >>= \res ->
  peekEnumUtil  a3'>>= \a3'' -> 
  peekBoolUtil  a4'>>= \a4'' -> 
  return (a3'', a4'')
{-# LINE 311 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getWorldSpaceCorners -}
getWorldSpaceCorners :: HG3DClass -> IO (Vec3)
getWorldSpaceCorners a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getWorldSpaceCorners'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 316 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

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

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

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

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

{- function synchroniseBaseSettingsWith -}
synchroniseBaseSettingsWith :: HG3DClass -> HG3DClass -> IO ()
synchroniseBaseSettingsWith a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  synchroniseBaseSettingsWith'_ a1' a2' >>= \res ->
  return ()
{-# LINE 341 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getPositionForViewUpdate -}
getPositionForViewUpdate :: HG3DClass -> IO (Vec3)
getPositionForViewUpdate a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getPositionForViewUpdate'_ a1' a2' >>= \res ->
  peekVec3  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 346 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

{- function getOrientationForViewUpdate -}
getOrientationForViewUpdate :: HG3DClass -> IO (Quaternion)
getOrientationForViewUpdate a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getOrientationForViewUpdate'_ a1' a2' >>= \res ->
  peekQuaternion  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 351 ".\\HGamer3D\\Bindings\\Ogre\\ClassCamera.chs" #-}

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

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

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


foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_construct"
  new'_ :: ((Ptr CChar) -> ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))))

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getSceneManager"
  getSceneManager'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setPosition"
  setPosition'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setPosition2"
  setPosition2'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getPosition"
  getPosition'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_move"
  move'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_moveRelative"
  moveRelative'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setDirection"
  setDirection'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setDirection2"
  setDirection2'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getDirection"
  getDirection'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getUp"
  getUp'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getRight"
  getRight'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_lookAt"
  lookAt'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_lookAt2"
  lookAt2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_roll"
  roll'_ :: ((HG3DClassPtr) -> ((RadiansPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_yaw"
  yaw'_ :: ((HG3DClassPtr) -> ((RadiansPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_pitch"
  pitch'_ :: ((HG3DClassPtr) -> ((RadiansPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_rotate"
  rotate'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> ((RadiansPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_rotate2"
  rotate2'_ :: ((HG3DClassPtr) -> ((QuaternionPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setFixedYawAxis"
  setFixedYawAxis'_ :: ((HG3DClassPtr) -> (CInt -> ((Vec3Ptr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getOrientation"
  getOrientation'_ :: ((HG3DClassPtr) -> ((QuaternionPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setOrientation"
  setOrientation'_ :: ((HG3DClassPtr) -> ((QuaternionPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getDerivedOrientation"
  getDerivedOrientation'_ :: ((HG3DClassPtr) -> ((QuaternionPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getDerivedPosition"
  getDerivedPosition'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getDerivedDirection"
  getDerivedDirection'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getDerivedUp"
  getDerivedUp'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getDerivedRight"
  getDerivedRight'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getRealOrientation"
  getRealOrientation'_ :: ((HG3DClassPtr) -> ((QuaternionPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getRealPosition"
  getRealPosition'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getRealDirection"
  getRealDirection'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getRealUp"
  getRealUp'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getRealRight"
  getRealRight'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getMovableType"
  getMovableType'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setLodBias"
  setLodBias'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getLodBias"
  getLodBias'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setLodCamera"
  setLodCamera'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getLodCamera"
  getLodCamera'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setWindow"
  setWindow'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> (IO ()))))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_resetWindow"
  resetWindow'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_isWindowSet"
  isWindowSet'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getBoundingRadius"
  getBoundingRadius'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getAutoTrackTarget"
  getAutoTrackTarget'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getAutoTrackOffset"
  getAutoTrackOffset'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setAutoAspectRatio"
  setAutoAspectRatio'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getAutoAspectRatio"
  getAutoAspectRatio'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setCullingFrustum"
  setCullingFrustum'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getCullingFrustum"
  getCullingFrustum'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_isVisible3"
  isVisible3'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> ((Ptr CInt) -> ((Ptr CInt) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getWorldSpaceCorners"
  getWorldSpaceCorners'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getNearClipDistance"
  getNearClipDistance'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getFarClipDistance"
  getFarClipDistance'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setUseRenderingDistance"
  setUseRenderingDistance'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getUseRenderingDistance"
  getUseRenderingDistance'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_synchroniseBaseSettingsWith"
  synchroniseBaseSettingsWith'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getPositionForViewUpdate"
  getPositionForViewUpdate'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getOrientationForViewUpdate"
  getOrientationForViewUpdate'_ :: ((HG3DClassPtr) -> ((QuaternionPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_setUseMinPixelSize"
  setUseMinPixelSize'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getUseMinPixelSize"
  getUseMinPixelSize'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassCamera.chs.h ogre_cam_getPixelDisplayRatio"
  getPixelDisplayRatio'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))