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


-- ClassEntity.chs

-- 

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

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

-- | Gets the MeshEntity
getMesh :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (SharedPtr)
 -- ^ 
getMesh a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getMesh'_ a1' a2' >>= \res ->
  peekSharedPtr  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 54 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Retrieves the number of SubEntity objects making up this entity. 
getNumSubEntities :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getNumSubEntities a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getNumSubEntities'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 59 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Clones this entity and returns a pointer to the clone. Useful method for duplicating an entity. The new entity must be given a unique name, and is not attached to the scene in any way so must be attached to a SceneNodeSceneManager::createEntity
clone :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ newName - Name for the new entity. 
  ->  IO (HG3DClass)
 -- ^ 
clone a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  clone'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 65 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Sets the material to use for the whole of this entity. This is a shortcut method to set all the materials for all subentities of this entity. Only use this method is you want to set the same material for all subentities or if you know there is only one. Otherwise call getSubEntity()
setMaterialName :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name
  ->  String  -- ^ groupName
  ->  IO ()
 -- ^ 
setMaterialName a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  setMaterialName'_ a1' a2' a3' >>= \res ->
  return ()
{-# LINE 71 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Sets the material to use for the whole of this entity. This is a shortcut method to set all the materials for all subentities of this entity. Only use this method is you want to set the same material for all subentities or if you know there is only one. Otherwise call getSubEntity()
setMaterial :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  SharedPtr  -- ^ material
  ->  IO ()
 -- ^ 
setMaterial a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withSharedPtr a2 $ \a2' -> 
  setMaterial'_ a1' a2' >>= \res ->
  return ()
{-# LINE 76 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Overridden from MovableObject
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 81 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | For entities based on animated meshes, gets the AnimationStateYou animate an entity by updating the animation state objects. Each of these represents the current state of each animation available to the entity. The AnimationStateMesh
getAnimationState :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ name
  ->  IO (HG3DClass)
 -- ^ 
getAnimationState a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  getAnimationState'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 87 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | For entities based on animated meshes, gets the AnimationStateYou animate an entity by updating the animation state objects. Each of these represents the current state of each animation available to the entity. The AnimationStateMesh
getAllAnimationStates :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (HG3DClass)
 -- ^ return value - In case the entity is animated, this functions returns the pointer to a     
getAllAnimationStates a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getAllAnimationStates'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 92 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Tells the Entity
setDisplaySkeleton :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ display
  ->  IO ()
 -- ^ 
setDisplaySkeleton a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setDisplaySkeleton'_ a1' a2' >>= \res ->
  return ()
{-# LINE 97 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Returns whether or not the entity is currently displaying its skeleton. 
getDisplaySkeleton :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
getDisplaySkeleton a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getDisplaySkeleton'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 102 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Gets a pointer to the entity representing the numbered manual level of detail. The zero-based index never includes the original entity, unlike Mesh::getLodLevel
getManualLodLevel :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Int  -- ^ index
  ->  IO (HG3DClass)
 -- ^ 
getManualLodLevel a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getManualLodLevel'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 108 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Returns the number of manual levels of detail that this entity supports. This number never includes the original entity, it is difference with Mesh::getNumLodLevels
getNumManualLodLevels :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getNumManualLodLevels a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getNumManualLodLevels'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 113 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Sets whether the polygon mode of this entire entity may be overridden by the camera detail settings. 
setPolygonModeOverrideable :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ PolygonModeOverrideable
  ->  IO ()
 -- ^ 
setPolygonModeOverrideable a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setPolygonModeOverrideable'_ a1' a2' >>= \res ->
  return ()
{-# LINE 118 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Detach a MovableObject
detachObjectFromBone :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  String  -- ^ movableName - is the name of the movable object to be detached. 
  ->  IO (HG3DClass)
 -- ^ 
detachObjectFromBone a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  detachObjectFromBone'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 124 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Detaches an object by pointer. Use this method to destroy a MovableObject
detachObjectFromBone2 :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  HG3DClass  -- ^ obj
  ->  IO ()
 -- ^ 
detachObjectFromBone2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  detachObjectFromBone2'_ a1' a2' >>= \res ->
  return ()
{-# LINE 129 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Detach all MovableObjects previously attached using attachObjectToBone. 
detachAllObjectsFromBone :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
detachAllObjectsFromBone a1 =
  withHG3DClass a1 $ \a1' -> 
  detachAllObjectsFromBone'_ a1' >>= \res ->
  return ()
{-# LINE 133 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | MovableObject::getBoundingRadius
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 138 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.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 143 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Returns whether or not this entity is skeletally animated. 
hasSkeleton :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
hasSkeleton a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  hasSkeleton'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 148 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Returns whether or not hardware animation is enabled. Because fixed-function indexed vertex blending is rarely supported by existing graphics cards, hardware animation can only be done if the vertex programs in the materials used to render an entity support it. Therefore, this method will only return true if all the materials assigned to this entity have vertex programs assigned, and all those vertex programs must support 'includes_morph_animation true' if using morph animation, 'includes_pose_animation true' if using pose animation and 'includes_skeletal_animation true' if using skeletal animation. 
isHardwareAnimationEnabled :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
isHardwareAnimationEnabled a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isHardwareAnimationEnabled'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 153 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Returns the number of requests that have been made for software animation If non-zero then software animation will be performed in updateAnimation regardless of the current setting of isHardwareAnimationEnabled or any internal optimise for eliminate software animation. Requests for software animation are made by calling the addSoftwareAnimationRequest()
getSoftwareAnimationRequests :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getSoftwareAnimationRequests a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSoftwareAnimationRequests'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 158 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Returns the number of requests that have been made for software animation of normals If non-zero, and getSoftwareAnimationRequests()getSoftwareAnimationRequests()addSoftwareAnimationRequest()
getSoftwareAnimationNormalsRequests :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Int)
 -- ^ 
getSoftwareAnimationNormalsRequests a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSoftwareAnimationNormalsRequests'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 163 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Add a request for software animation Tells the entity to perform animation calculations for skeletal/vertex animations in software, regardless of the current setting of isHardwareAnimationEnabled()removeSoftwareAnimationRequest()
addSoftwareAnimationRequest :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ normalsAlso
  ->  IO ()
 -- ^ 
addSoftwareAnimationRequest a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  addSoftwareAnimationRequest'_ a1' a2' >>= \res ->
  return ()
{-# LINE 168 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Removes a request for software animation Calling this decrements the entity's internal counter of the number of requests for software animation. If the counter is already zero then calling this method throws an exception. The 'normalsAlso' flag if set to 'true' will also decrement the internal counter of number of requests for software animation of normals. 
removeSoftwareAnimationRequest :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ normalsAlso
  ->  IO ()
 -- ^ 
removeSoftwareAnimationRequest a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  removeSoftwareAnimationRequest'_ a1' a2' >>= \res ->
  return ()
{-# LINE 173 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Shares the SkeletonInstance with the supplied entity. Note that in order for this to work, both entities must have the same Skeleton
shareSkeletonInstanceWith :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  HG3DClass  -- ^ entity
  ->  IO ()
 -- ^ 
shareSkeletonInstanceWith a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  shareSkeletonInstanceWith'_ a1' a2' >>= \res ->
  return ()
{-# LINE 178 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Returns whether or not this entity is either morph or pose animated. 
hasVertexAnimation :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
hasVertexAnimation a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  hasVertexAnimation'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 183 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Stops sharing the SkeletonInstance with other entities. 
stopSharingSkeletonInstance :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
stopSharingSkeletonInstance a1 =
  withHG3DClass a1 $ \a1' -> 
  stopSharingSkeletonInstance'_ a1' >>= \res ->
  return ()
{-# LINE 187 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Returns whether this entity shares it's SkeltonInstance with other entity instances. 
sharesSkeletonInstance :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
sharesSkeletonInstance a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  sharesSkeletonInstance'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 192 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Updates the internal animation state set to include the latest available animations from the attached skeleton. Use this method if you manually add animations to a skeleton, or have linked the skeleton to another for animation purposes since creating this entity. If you have called getAnimationState prior to calling this method, the pointers will still remain valid. 
refreshAvailableAnimationState :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO ()
 -- ^ 
refreshAvailableAnimationState a1 =
  withHG3DClass a1 $ \a1' -> 
  refreshAvailableAnimationState'_ a1' >>= \res ->
  return ()
{-# LINE 196 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Choose which vertex data to bind to the renderer. 
chooseVertexDataForBinding :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ hasVertexAnim
  ->  IO (EnumEntityVertexDataBindChoice)
 -- ^ 
chooseVertexDataForBinding a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  alloca $ \a3' -> 
  chooseVertexDataForBinding'_ a1' a2' a3' >>= \res ->
  peekEnumUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 202 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Has this EntityIf this returns false, it means this EntityMeshSkeletonEntity
isInitialised :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  IO (Bool)
 -- ^ 
isInitialised a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isInitialised'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 207 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | Resource::ListenerEntityMesh
backgroundLoadingComplete :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  HG3DClass  -- ^ res
  ->  IO ()
 -- ^ 
backgroundLoadingComplete a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  backgroundLoadingComplete'_ a1' a2' >>= \res ->
  return ()
{-# LINE 212 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

-- | EntityAnimationStateAnimationState
setSkipAnimationStateUpdate :: HG3DClass  -- ^ classpointer - pointer of Class instance from which this methods is called.
  ->  Bool  -- ^ skip
  ->  IO ()
 -- ^ 
setSkipAnimationStateUpdate a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setSkipAnimationStateUpdate'_ a1' a2' >>= \res ->
  return ()
{-# LINE 217 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

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


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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_getMesh"
  getMesh'_ :: ((HG3DClassPtr) -> ((SharedPtrPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_getNumSubEntities"
  getNumSubEntities'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_clone"
  clone'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_setMaterial"
  setMaterial'_ :: ((HG3DClassPtr) -> ((SharedPtrPtr) -> (IO ())))

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_getAnimationState"
  getAnimationState'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_getAllAnimationStates"
  getAllAnimationStates'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_setDisplaySkeleton"
  setDisplaySkeleton'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_getDisplaySkeleton"
  getDisplaySkeleton'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_getManualLodLevel"
  getManualLodLevel'_ :: ((HG3DClassPtr) -> (CInt -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_getNumManualLodLevels"
  getNumManualLodLevels'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_setPolygonModeOverrideable"
  setPolygonModeOverrideable'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_detachObjectFromBone"
  detachObjectFromBone'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_detachObjectFromBone2"
  detachObjectFromBone2'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_detachAllObjectsFromBone"
  detachAllObjectsFromBone'_ :: ((HG3DClassPtr) -> (IO ()))

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

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

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_hasSkeleton"
  hasSkeleton'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_isHardwareAnimationEnabled"
  isHardwareAnimationEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_getSoftwareAnimationRequests"
  getSoftwareAnimationRequests'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_getSoftwareAnimationNormalsRequests"
  getSoftwareAnimationNormalsRequests'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_addSoftwareAnimationRequest"
  addSoftwareAnimationRequest'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_removeSoftwareAnimationRequest"
  removeSoftwareAnimationRequest'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_shareSkeletonInstanceWith"
  shareSkeletonInstanceWith'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_hasVertexAnimation"
  hasVertexAnimation'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_stopSharingSkeletonInstance"
  stopSharingSkeletonInstance'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_sharesSkeletonInstance"
  sharesSkeletonInstance'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_refreshAvailableAnimationState"
  refreshAvailableAnimationState'_ :: ((HG3DClassPtr) -> (IO ()))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_chooseVertexDataForBinding"
  chooseVertexDataForBinding'_ :: ((HG3DClassPtr) -> (CInt -> ((Ptr CInt) -> (IO ()))))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_isInitialised"
  isInitialised'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_backgroundLoadingComplete"
  backgroundLoadingComplete'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_setSkipAnimationStateUpdate"
  setSkipAnimationStateUpdate'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))

foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassEntity.chs.h ogre_ent_getSkipAnimationStateUpdate"
  getSkipAnimationStateUpdate'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))