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


-- ClassFrustum.chs

-- 

module HGamer3D.Bindings.Ogre.ClassFrustum 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\\ClassFrustum.chs" #-}
import HGamer3D.Bindings.Ogre.ClassPtr
{-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}
import HGamer3D.Bindings.Ogre.StructHG3DClass
{-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}
import HGamer3D.Bindings.Ogre.StructRadians
{-# LINE 45 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}
import HGamer3D.Bindings.Ogre.StructVec2
{-# LINE 46 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}
import HGamer3D.Bindings.Ogre.StructVec3
{-# LINE 47 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}
import HGamer3D.Bindings.Ogre.EnumFrustumPlane
{-# LINE 48 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}
import HGamer3D.Bindings.Ogre.StructSharedPtr
{-# LINE 49 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}
import HGamer3D.Bindings.Ogre.EnumProjectionType
{-# LINE 50 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}
import HGamer3D.Bindings.Ogre.StructQuaternion
{-# LINE 51 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}
import HGamer3D.Bindings.Ogre.EnumOrientationMode
{-# LINE 52 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}

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

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

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

{- function getFOVy -}
getFOVy :: HG3DClass -> IO (Radians)
getFOVy a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getFOVy'_ a1' a2' >>= \res ->
  peekRadians  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 72 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}

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

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

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

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

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

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

{- function setFrustumOffset -}
setFrustumOffset :: HG3DClass -> Vec2 -> IO ()
setFrustumOffset a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec2 a2 $ \a2' -> 
  setFrustumOffset'_ a1' a2' >>= \res ->
  return ()
{-# LINE 107 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}

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

{- function getFrustumOffset -}
getFrustumOffset :: HG3DClass -> IO (Vec2)
getFrustumOffset a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getFrustumOffset'_ a1' a2' >>= \res ->
  peekVec2  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 118 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}

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

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

{- function setFrustumExtents -}
setFrustumExtents :: HG3DClass -> Float -> Float -> Float -> Float -> IO ()
setFrustumExtents 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 
  setFrustumExtents'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 136 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}

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

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

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

{- function isCustomProjectionMatrixEnabled -}
isCustomProjectionMatrixEnabled :: HG3DClass -> IO (Bool)
isCustomProjectionMatrixEnabled a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isCustomProjectionMatrixEnabled'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 158 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.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 165 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}

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

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

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

{- function getMaterial -}
getMaterial :: HG3DClass -> IO (SharedPtr)
getMaterial a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getMaterial'_ a1' a2' >>= \res ->
  peekSharedPtr  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 185 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}

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

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

{- function setProjectionType -}
setProjectionType :: HG3DClass -> EnumProjectionType -> IO ()
setProjectionType a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = cIntFromEnum a2} in 
  setProjectionType'_ a1' a2' >>= \res ->
  return ()
{-# LINE 201 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}

{- function getProjectionType -}
getProjectionType :: HG3DClass -> IO (EnumProjectionType)
getProjectionType a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getProjectionType'_ a1' a2' >>= \res ->
  peekEnumUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 206 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}

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

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

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

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

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

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

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

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

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

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

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

{- function setOrientationMode -}
setOrientationMode :: HG3DClass -> EnumOrientationMode -> IO ()
setOrientationMode a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = cIntFromEnum a2} in 
  setOrientationMode'_ a1' a2' >>= \res ->
  return ()
{-# LINE 265 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}

{- function getOrientationMode -}
getOrientationMode :: HG3DClass -> IO (EnumOrientationMode)
getOrientationMode a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getOrientationMode'_ a1' a2' >>= \res ->
  peekEnumUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 270 ".\\HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs" #-}


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

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setFOVy"
  setFOVy'_ :: ((HG3DClassPtr) -> ((RadiansPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getFOVy"
  getFOVy'_ :: ((HG3DClassPtr) -> ((RadiansPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setNearClipDistance"
  setNearClipDistance'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setFarClipDistance"
  setFarClipDistance'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setAspectRatio"
  setAspectRatio'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getAspectRatio"
  getAspectRatio'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setFrustumOffset"
  setFrustumOffset'_ :: ((HG3DClassPtr) -> ((Vec2Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setFrustumOffset2"
  setFrustumOffset2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getFrustumOffset"
  getFrustumOffset'_ :: ((HG3DClassPtr) -> ((Vec2Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setFocalLength"
  setFocalLength'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getFocalLength"
  getFocalLength'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setFrustumExtents"
  setFrustumExtents'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> (IO ()))))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_resetFrustumExtents"
  resetFrustumExtents'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getFrustumExtents"
  getFrustumExtents'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> ((Ptr CFloat) -> (IO ()))))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_isCustomViewMatrixEnabled"
  isCustomViewMatrixEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_isCustomProjectionMatrixEnabled"
  isCustomProjectionMatrixEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getTypeFlags"
  getTypeFlags'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

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

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getMaterial"
  getMaterial'_ :: ((HG3DClassPtr) -> ((SharedPtrPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getSquaredViewDepth"
  getSquaredViewDepth'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))))

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setProjectionType"
  setProjectionType'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getProjectionType"
  getProjectionType'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setOrthoWindow"
  setOrthoWindow'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setOrthoWindowHeight"
  setOrthoWindowHeight'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setOrthoWindowWidth"
  setOrthoWindowWidth'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getOrthoWindowHeight"
  getOrthoWindowHeight'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getOrthoWindowWidth"
  getOrthoWindowWidth'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_disableReflection"
  disableReflection'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_isReflected"
  isReflected'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_disableCustomNearClipPlane"
  disableCustomNearClipPlane'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_isCustomNearClipPlaneEnabled"
  isCustomNearClipPlaneEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

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

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_setOrientationMode"
  setOrientationMode'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassFrustum.chs.h ogre_frst_getOrientationMode"
  getOrientationMode'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))