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


-- ClassManualObject.chs

-- 

module HGamer3D.Bindings.Ogre.ClassManualObject 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\\ClassManualObject.chs" #-}
import HGamer3D.Bindings.Ogre.ClassPtr
{-# LINE 41 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}
import HGamer3D.Bindings.Ogre.StructHG3DClass
{-# LINE 42 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}
import HGamer3D.Bindings.Ogre.EnumRenderOperationOperationType
{-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}
import HGamer3D.Bindings.Ogre.StructVec3
{-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}
import HGamer3D.Bindings.Ogre.StructVec2
{-# LINE 45 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}
import HGamer3D.Bindings.Ogre.StructColour
{-# LINE 46 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}
import HGamer3D.Bindings.Ogre.StructSharedPtr
{-# LINE 47 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | 
new :: String  -- ^ name
  ->  IO (HG3DClass)
 -- ^ 
new a1 =
  withCString a1 $ \a1' -> 
  alloca $ \a2' -> 
  new'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 53 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.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 57 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Completely clear the contents of the object. Clearing the contents of this object and rebuilding from scratch is not the optimal way to manage dynamic vertex data, since the buffers are recreated. If you want to keep the same structure but update the content within that structure, use beginUpdate()clear()begin()
clear :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
clear a1 =
  withHG3DClass a1 $ \a1' -> 
  clear'_ a1' >>= \res ->
  return ()
{-# LINE 61 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Estimate the number of vertices ahead of time. Calling this helps to avoid memory reallocation when you define vertices. Also very handy when using beginUpdate()
estimateVertexCount :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ vcount
  ->  IO ()
 -- ^ 
estimateVertexCount a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  estimateVertexCount'_ a1' a2' >>= \res ->
  return ()
{-# LINE 66 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Estimate the number of indices ahead of time. Calling this helps to avoid memory reallocation when you define indices. Also very handy when using beginUpdate()
estimateIndexCount :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ icount
  ->  IO ()
 -- ^ 
estimateIndexCount a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  estimateIndexCount'_ a1' a2' >>= \res ->
  return ()
{-# LINE 71 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Start defining a part of the object. Each time you call this method, you start a new section of the object with its own material and potentially its own type of rendering operation (triangles, points or lines for example). 
begin :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ materialName - The name of the material to render this part of the object with. 
  ->  EnumRenderOperationOperationType  -- ^ opType - The type of operation to use to render. 
  ->  String  -- ^ groupName
  ->  IO ()
 -- ^ 
begin a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  let {a3' = cIntFromEnum a3} in 
  withCString a4 $ \a4' -> 
  begin'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 78 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Use before defining geometry to indicate that you intend to update the geometry regularly and want the internal structure to reflect that. 
setDynamic :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ dyn
  ->  IO ()
 -- ^ 
setDynamic a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setDynamic'_ a1' a2' >>= \res ->
  return ()
{-# LINE 83 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Gets whether this object is marked as dynamic 
getDynamic :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
getDynamic a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDynamic'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 88 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Start the definition of an update to a part of the object. Using this method, you can update an existing section of the object efficiently. You do not have the option of changing the operation type obviously, since it must match the one that was used before. If your sections are changing size, particularly growing, use estimateVertexCount and estimateIndexCount to pre-size the buffers a little larger than the initial needs to avoid buffer reconstruction. 
beginUpdate :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ sectionIndex - The index of the section you want to update. The first call to begin() would have created section 0, the second section 1, etc. 
  ->  IO ()
 -- ^ 
beginUpdate a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  beginUpdate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 93 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a vertex position, starting a new vertex at the same time. A vertex position is slightly special among the other vertex data methods like normal()textureCoord()position()
position :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Vec3  -- ^ pos
  ->  IO ()
 -- ^ 
position a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  position'_ a1' a2' >>= \res ->
  return ()
{-# LINE 98 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a vertex position, starting a new vertex at the same time. A vertex position is slightly special among the other vertex data methods like normal()textureCoord()position()
position2 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ x
  ->  Float  -- ^ y
  ->  Float  -- ^ z
  ->  IO ()
 -- ^ 
position2 a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  position2'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 105 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a vertex normal to the current vertex. Vertex normals are most often used for dynamic lighting, and their components should be normalised. 
normal :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Vec3  -- ^ norm
  ->  IO ()
 -- ^ 
normal a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  normal'_ a1' a2' >>= \res ->
  return ()
{-# LINE 110 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a vertex normal to the current vertex. Vertex normals are most often used for dynamic lighting, and their components should be normalised. 
normal2 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ x
  ->  Float  -- ^ y
  ->  Float  -- ^ z
  ->  IO ()
 -- ^ 
normal2 a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  normal2'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 117 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a vertex tangent to the current vertex. Vertex tangents are most often used for dynamic lighting, and their components should be normalised. Also, using tangent()
tangent :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Vec3  -- ^ tan
  ->  IO ()
 -- ^ 
tangent a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  tangent'_ a1' a2' >>= \res ->
  return ()
{-# LINE 122 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a vertex tangent to the current vertex. Vertex tangents are most often used for dynamic lighting, and their components should be normalised. Also, using tangent()
tangent2 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ x
  ->  Float  -- ^ y
  ->  Float  -- ^ z
  ->  IO ()
 -- ^ 
tangent2 a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  tangent2'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 129 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a texture coordinate to the current vertex. You can call this method multiple times between position()
textureCoord :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ u
  ->  IO ()
 -- ^ 
textureCoord a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  textureCoord'_ a1' a2' >>= \res ->
  return ()
{-# LINE 134 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a texture coordinate to the current vertex. You can call this method multiple times between position()
textureCoord2 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ u
  ->  Float  -- ^ v
  ->  IO ()
 -- ^ 
textureCoord2 a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  textureCoord2'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 140 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a texture coordinate to the current vertex. You can call this method multiple times between position()
textureCoord3 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ u
  ->  Float  -- ^ v
  ->  Float  -- ^ w
  ->  IO ()
 -- ^ 
textureCoord3 a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  let {a3' = realToFrac a3} in 
  let {a4' = realToFrac a4} in 
  textureCoord3'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 147 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a texture coordinate to the current vertex. You can call this method multiple times between position()
textureCoord4 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ x
  ->  Float  -- ^ y
  ->  Float  -- ^ z
  ->  Float  -- ^ w
  ->  IO ()
 -- ^ 
textureCoord4 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 
  textureCoord4'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 155 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a texture coordinate to the current vertex. You can call this method multiple times between position()
textureCoord5 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Vec2  -- ^ uv
  ->  IO ()
 -- ^ 
textureCoord5 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec2 a2 $ \a2' -> 
  textureCoord5'_ a1' a2' >>= \res ->
  return ()
{-# LINE 160 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a texture coordinate to the current vertex. You can call this method multiple times between position()
textureCoord6 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Vec3  -- ^ uvw
  ->  IO ()
 -- ^ 
textureCoord6 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withVec3 a2 $ \a2' -> 
  textureCoord6'_ a1' a2' >>= \res ->
  return ()
{-# LINE 165 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a vertex colour to a vertex. 
colour :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Colour  -- ^ col
  ->  IO ()
 -- ^ 
colour a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withColour a2 $ \a2' -> 
  colour'_ a1' a2' >>= \res ->
  return ()
{-# LINE 170 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a vertex colour to a vertex. 
colour2 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Float  -- ^ r - Colour components expressed as floating point numbers from 0-1 
  ->  Float  -- ^ g
  ->  Float  -- ^ b
  ->  Float  -- ^ a
  ->  IO ()
 -- ^ 
colour2 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 
  colour2'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 178 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a vertex index to construct faces / lines / points via indexing rather than just by a simple list of vertices. You will have to call this 3 times for each face for a triangle list, or use the alternative 3-parameter version. Other operation types require different numbers of indexes, RenderOperation::OperationType32-bit indexes are not supported on all cards and will only be used when required, if an index is > 65535. 
index :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ idx - A vertex index from 0 to 4294967295. 
  ->  IO ()
 -- ^ 
index a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  index'_ a1' a2' >>= \res ->
  return ()
{-# LINE 183 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a set of 3 vertex indices to construct a triangle; this is a shortcut to calling index()32-bit indexes are not supported on all cards and will only be used when required, if an index is > 65535. 
triangle :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ i1 - 3 vertex indices from 0 to 4294967295 defining a face. 
  ->  Int  -- ^ i2
  ->  Int  -- ^ i3
  ->  IO ()
 -- ^ 
triangle a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  triangle'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 190 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Add a set of 4 vertex indices to construct a quad (out of 2 triangles); this is a shortcut to calling index()triangle()32-bit indexes are not supported on all cards and will only be used when required, if an index is > 65535. 
quad :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ i1 - 3 vertex indices from 0 to 4294967295 defining a face. 
  ->  Int  -- ^ i2
  ->  Int  -- ^ i3
  ->  Int  -- ^ i4
  ->  IO ()
 -- ^ 
quad a1 a2 a3 a4 a5 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  let {a3' = fromIntegral a3} in 
  let {a4' = fromIntegral a4} in 
  let {a5' = fromIntegral a5} in 
  quad'_ a1' a2' a3' a4' a5' >>= \res ->
  return ()
{-# LINE 198 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Finish defining the object and compile the final renderable version. Will return a pointer to the finished section or NULL if the section was discarded (i.e. has zero vertices/indices). 
end :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (HG3DClass)
 -- ^ 
end a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  end'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 203 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Alter the material for a subsection of this object after it has been specified. You specify the material to use on a section of this object during the call to begin()
setMaterialName :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ subindex
  ->  String  -- ^ name - The name of the new material to use 
  ->  String  -- ^ group
  ->  IO ()
 -- ^ 
setMaterialName a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  withCString a3 $ \a3' -> 
  withCString a4 $ \a4' -> 
  setMaterialName'_ a1' a2' a3' a4' >>= \res ->
  return ()
{-# LINE 210 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Convert this object to a MeshAfter you've finished building this object, you may convert it to a MeshEntitySceneNodeOnly objects which use indexed geometry may be converted to a mesh. 
convertToMesh :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ meshName - The name to give the mesh 
  ->  String  -- ^ groupName - The resource group to create the mesh in 
  ->  IO (SharedPtr)
 -- ^ 
convertToMesh a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  alloca $ \a4' -> 
  convertToMesh'_ a1' a2' a3' a4' >>= \res ->
  peekSharedPtr  a4'>>= \a4'' -> 
  return (a4'')
{-# LINE 217 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Sets whether or not to use an 'identity' projection. Usually ManualObjects will use a projection matrix as determined by the active camera. However, if they want they can cancel this out and use an identity projection, which effectively projects in 2D using a {-1, 1} view space. Useful for overlay rendering. Normally you don't need to change this. The default is false. ManualObject::getUseIdentityProjection
setUseIdentityProjection :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ useIdentityProjection
  ->  IO ()
 -- ^ 
setUseIdentityProjection a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setUseIdentityProjection'_ a1' a2' >>= \res ->
  return ()
{-# LINE 222 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Returns whether or not to use an 'identity' projection. Usually ManualObjects will use a projection matrix as determined by the active camera. However, if they want they can cancel this out and use an identity projection, which effectively projects in 2D using a {-1, 1} view space. Useful for overlay rendering. Normally you don't need to change this. ManualObject::setUseIdentityProjection
getUseIdentityProjection :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
getUseIdentityProjection a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getUseIdentityProjection'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 227 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Sets whether or not to use an 'identity' view. Usually ManualObjects will use a view matrix as determined by the active camera. However, if they want they can cancel this out and use an identity matrix, which means all geometry is assumed to be relative to camera space already. Useful for overlay rendering. Normally you don't need to change this. The default is false. ManualObject::getUseIdentityView
setUseIdentityView :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ useIdentityView
  ->  IO ()
 -- ^ 
setUseIdentityView a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setUseIdentityView'_ a1' a2' >>= \res ->
  return ()
{-# LINE 232 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Returns whether or not to use an 'identity' view. Usually ManualObjects will use a view matrix as determined by the active camera. However, if they want they can cancel this out and use an identity matrix, which means all geometry is assumed to be relative to camera space already. Useful for overlay rendering. Normally you don't need to change this. ManualObject::setUseIdentityView
getUseIdentityView :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
getUseIdentityView a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getUseIdentityView'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 237 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Gets a pointer to a ManualObjectSectionManualObject
getSection :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ index
  ->  IO (HG3DClass)
 -- ^ 
getSection a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getSection'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 243 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

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

-- | Sets whether or not to keep the original declaration order when queuing the renderables. This overrides the default behavior of the rendering queue, specifically stating the desired order of rendering. Might result in a performance loss, but lets the user to have more direct control when creating geometry through this class. 
setKeepDeclarationOrder :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ keepOrder - Whether to keep the declaration order or not. 
  ->  IO ()
 -- ^ 
setKeepDeclarationOrder a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setKeepDeclarationOrder'_ a1' a2' >>= \res ->
  return ()
{-# LINE 253 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | Gets whether or not the declaration order is to be kept or not. 
getKeepDeclarationOrder :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ return value - A flag indication if the declaration order will be kept when queuing the renderables.     
getKeepDeclarationOrder a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getKeepDeclarationOrder'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 258 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | .  - Details: Returns the type name of this object. 
getMovableType :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (String)
 -- ^ 
getMovableType a1 =
  withHG3DClass a1 $ \a1' -> 
  alloc64k $ \a2' -> 
  getMovableType'_ a1' a2' >>= \res ->
  peekCString  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 263 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

-- | .  - Details: Retrieves the radius of the origin-centered bounding sphere for this object. 
getBoundingRadius :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Float)
 -- ^ 
getBoundingRadius a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getBoundingRadius'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 268 ".\\HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs" #-}

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


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

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_clear"
  clear'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_estimateVertexCount"
  estimateVertexCount'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_estimateIndexCount"
  estimateIndexCount'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_begin"
  begin'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CInt -> ((Ptr CChar) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_setDynamic"
  setDynamic'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_getDynamic"
  getDynamic'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_beginUpdate"
  beginUpdate'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_position"
  position'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_position2"
  position2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_normal"
  normal'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_normal2"
  normal2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_tangent"
  tangent'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_tangent2"
  tangent2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_textureCoord"
  textureCoord'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_textureCoord2"
  textureCoord2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_textureCoord3"
  textureCoord3'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_textureCoord4"
  textureCoord4'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> (IO ()))))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_textureCoord5"
  textureCoord5'_ :: ((HG3DClassPtr) -> ((Vec2Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_textureCoord6"
  textureCoord6'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_colour"
  colour'_ :: ((HG3DClassPtr) -> ((ColourPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_colour2"
  colour2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> (IO ()))))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_index"
  index'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_triangle"
  triangle'_ :: ((HG3DClassPtr) -> (CUInt -> (CUInt -> (CUInt -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_quad"
  quad'_ :: ((HG3DClassPtr) -> (CUInt -> (CUInt -> (CUInt -> (CUInt -> (IO ()))))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_end"
  end'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_setMaterialName"
  setMaterialName'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_convertToMesh"
  convertToMesh'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((SharedPtrPtr) -> (IO ())))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_setUseIdentityProjection"
  setUseIdentityProjection'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_getUseIdentityProjection"
  getUseIdentityProjection'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_setUseIdentityView"
  setUseIdentityView'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_getUseIdentityView"
  getUseIdentityView'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_getSection"
  getSection'_ :: ((HG3DClassPtr) -> (CUInt -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_getNumSections"
  getNumSections'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_setKeepDeclarationOrder"
  setKeepDeclarationOrder'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_getKeepDeclarationOrder"
  getKeepDeclarationOrder'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

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

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassManualObject.chs.h ogre_mno_hasEdgeList"
  hasEdgeList'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))