-- 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" #-}

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

{- function getMesh -}
getMesh :: HG3DClass -> 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" #-}

{- function getNumSubEntities -}
getNumSubEntities :: HG3DClass -> 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" #-}

{- function clone -}
clone :: HG3DClass -> String -> 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" #-}

{- function setMaterialName -}
setMaterialName :: HG3DClass -> String -> String -> 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" #-}

{- function setMaterial -}
setMaterial :: HG3DClass -> SharedPtr -> IO ()
setMaterial a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withSharedPtr a2 $ \a2' -> 
  setMaterial'_ a1' a2' >>= \res ->
  return ()
{-# LINE 76 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

{- function getMovableType -}
getMovableType :: HG3DClass -> 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" #-}

{- function getAnimationState -}
getAnimationState :: HG3DClass -> String -> 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" #-}

{- function hasAnimationState -}
hasAnimationState :: HG3DClass -> String -> IO (Bool)
hasAnimationState a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  hasAnimationState'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
{-# LINE 93 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

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

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

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

{- function getManualLodLevel -}
getManualLodLevel :: HG3DClass -> Int -> 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 114 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

{- function chooseVertexDataForBinding -}
chooseVertexDataForBinding :: HG3DClass -> Bool -> 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 208 ".\\HGamer3D\\Bindings\\Ogre\\ClassEntity.chs" #-}

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

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

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

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

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

{- function getAlwaysUpdateMainSkeleton -}
getAlwaysUpdateMainSkeleton :: HG3DClass -> IO (Bool)
getAlwaysUpdateMainSkeleton a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getAlwaysUpdateMainSkeleton'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
{-# LINE 238 ".\\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_hasAnimationState"
  hasAnimationState'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (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 ())))

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

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