module HGamer3D.Bindings.Ogre.ClassMesh 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
import HGamer3D.Bindings.Ogre.ClassPtr
import HGamer3D.Bindings.Ogre.StructHG3DClass
import HGamer3D.Bindings.Ogre.StructSharedPtr
import HGamer3D.Bindings.Ogre.EnumVertexAnimationType
delete :: HG3DClass -> IO ()
delete a1 =
  withHG3DClass a1 $ \a1' -> 
  delete'_ a1' >>= \res ->
  return ()
unnameSubMesh :: HG3DClass -> String -> IO ()
unnameSubMesh a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  unnameSubMesh'_ a1' a2' >>= \res ->
  return ()
getNumSubMeshes :: HG3DClass -> IO (Int)
getNumSubMeshes a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getNumSubMeshes'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
destroySubMesh :: HG3DClass -> Int -> IO ()
destroySubMesh a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  destroySubMesh'_ a1' a2' >>= \res ->
  return ()
destroySubMesh2 :: HG3DClass -> String -> IO ()
destroySubMesh2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  destroySubMesh2'_ a1' a2' >>= \res ->
  return ()
clone :: HG3DClass -> String -> String -> IO (SharedPtr)
clone a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  withCString a3 $ \a3' -> 
  alloca $ \a4' -> 
  clone'_ a1' a2' a3' a4' >>= \res ->
  peekSharedPtr  a4'>>= \a4'' -> 
  return (a4'')
getBoundingSphereRadius :: HG3DClass -> IO (Float)
getBoundingSphereRadius a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getBoundingSphereRadius'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
setSkeletonName :: HG3DClass -> String -> IO ()
setSkeletonName a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  setSkeletonName'_ a1' a2' >>= \res ->
  return ()
hasSkeleton :: HG3DClass -> IO (Bool)
hasSkeleton a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  hasSkeleton'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
hasVertexAnimation :: HG3DClass -> IO (Bool)
hasVertexAnimation a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  hasVertexAnimation'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
getSkeleton :: HG3DClass -> IO (SharedPtr)
getSkeleton a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSkeleton'_ a1' a2' >>= \res ->
  peekSharedPtr  a2'>>= \a2'' -> 
  return (a2'')
getSkeletonName :: HG3DClass -> IO (String)
getSkeletonName a1 =
  withHG3DClass a1 $ \a1' -> 
  alloc64k $ \a2' -> 
  getSkeletonName'_ a1' a2' >>= \res ->
  peekCString  a2'>>= \a2'' -> 
  return (a2'')
clearBoneAssignments :: HG3DClass -> IO ()
clearBoneAssignments a1 =
  withHG3DClass a1 $ \a1' -> 
  clearBoneAssignments'_ a1' >>= \res ->
  return ()
createManualLodLevel :: HG3DClass -> Float -> String -> String -> IO ()
createManualLodLevel a1 a2 a3 a4 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  withCString a3 $ \a3' -> 
  withCString a4 $ \a4' -> 
  createManualLodLevel'_ a1' a2' a3' a4' >>= \res ->
  return ()
isLodManual :: HG3DClass -> IO (Bool)
isLodManual a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isLodManual'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
removeLodLevels :: HG3DClass -> IO ()
removeLodLevels a1 =
  withHG3DClass a1 $ \a1' -> 
  removeLodLevels'_ a1' >>= \res ->
  return ()
isVertexBufferShadowed :: HG3DClass -> IO (Bool)
isVertexBufferShadowed a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isVertexBufferShadowed'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
isIndexBufferShadowed :: HG3DClass -> IO (Bool)
isIndexBufferShadowed a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isIndexBufferShadowed'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
buildEdgeList :: HG3DClass -> IO ()
buildEdgeList a1 =
  withHG3DClass a1 $ \a1' -> 
  buildEdgeList'_ a1' >>= \res ->
  return ()
freeEdgeList :: HG3DClass -> IO ()
freeEdgeList a1 =
  withHG3DClass a1 $ \a1' -> 
  freeEdgeList'_ a1' >>= \res ->
  return ()
prepareForShadowVolume :: HG3DClass -> IO ()
prepareForShadowVolume a1 =
  withHG3DClass a1 $ \a1' -> 
  prepareForShadowVolume'_ a1' >>= \res ->
  return ()
isPreparedForShadowVolumes :: HG3DClass -> IO (Bool)
isPreparedForShadowVolumes a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isPreparedForShadowVolumes'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
isEdgeListBuilt :: HG3DClass -> IO (Bool)
isEdgeListBuilt a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isEdgeListBuilt'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
setAutoBuildEdgeLists :: HG3DClass -> Bool -> IO ()
setAutoBuildEdgeLists a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setAutoBuildEdgeLists'_ a1' a2' >>= \res ->
  return ()
getAutoBuildEdgeLists :: HG3DClass -> IO (Bool)
getAutoBuildEdgeLists a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getAutoBuildEdgeLists'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
getSharedVertexDataAnimationType :: HG3DClass -> IO (EnumVertexAnimationType)
getSharedVertexDataAnimationType a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSharedVertexDataAnimationType'_ a1' a2' >>= \res ->
  peekEnumUtil  a2'>>= \a2'' -> 
  return (a2'')
getSharedVertexDataAnimationIncludesNormals :: HG3DClass -> IO (Bool)
getSharedVertexDataAnimationIncludesNormals a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getSharedVertexDataAnimationIncludesNormals'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
createAnimation :: HG3DClass -> String -> Float -> IO (HG3DClass)
createAnimation a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  alloca $ \a4' -> 
  createAnimation'_ a1' a2' a3' a4' >>= \res ->
  peek  a4'>>= \a4'' -> 
  return (a4'')
getAnimation :: HG3DClass -> String -> IO (HG3DClass)
getAnimation a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  getAnimation'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
hasAnimation :: HG3DClass -> String -> IO (Bool)
hasAnimation a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  hasAnimation'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
removeAnimation :: HG3DClass -> String -> IO ()
removeAnimation a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  removeAnimation'_ a1' a2' >>= \res ->
  return ()
getNumAnimations :: HG3DClass -> IO (Int)
getNumAnimations a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getNumAnimations'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
getAnimation2 :: HG3DClass -> Int -> IO (HG3DClass)
getAnimation2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getAnimation2'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
removeAllAnimations :: HG3DClass -> IO ()
removeAllAnimations a1 =
  withHG3DClass a1 $ \a1' -> 
  removeAllAnimations'_ a1' >>= \res ->
  return ()
updateMaterialForAllSubMeshes :: HG3DClass -> IO ()
updateMaterialForAllSubMeshes a1 =
  withHG3DClass a1 $ \a1' -> 
  updateMaterialForAllSubMeshes'_ a1' >>= \res ->
  return ()
getPoseCount :: HG3DClass -> IO (Int)
getPoseCount a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getPoseCount'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
removePose2 :: HG3DClass -> String -> IO ()
removePose2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  removePose2'_ a1' a2' >>= \res ->
  return ()
removeAllPoses :: HG3DClass -> IO ()
removeAllPoses a1 =
  withHG3DClass a1 $ \a1' -> 
  removeAllPoses'_ a1' >>= \res ->
  return ()
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_destruct"
  delete'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_unnameSubMesh"
  unnameSubMesh'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getNumSubMeshes"
  getNumSubMeshes'_ :: ((HG3DClassPtr) -> ((Ptr CUShort) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_destroySubMesh"
  destroySubMesh'_ :: ((HG3DClassPtr) -> (CUShort -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_destroySubMesh2"
  destroySubMesh2'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_clone"
  clone'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> ((SharedPtrPtr) -> (IO ())))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getBoundingSphereRadius"
  getBoundingSphereRadius'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_setSkeletonName"
  setSkeletonName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_hasSkeleton"
  hasSkeleton'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_hasVertexAnimation"
  hasVertexAnimation'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getSkeleton"
  getSkeleton'_ :: ((HG3DClassPtr) -> ((SharedPtrPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getSkeletonName"
  getSkeletonName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_clearBoneAssignments"
  clearBoneAssignments'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_createManualLodLevel"
  createManualLodLevel'_ :: ((HG3DClassPtr) -> (CFloat -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ())))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_isLodManual"
  isLodManual'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_removeLodLevels"
  removeLodLevels'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_isVertexBufferShadowed"
  isVertexBufferShadowed'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_isIndexBufferShadowed"
  isIndexBufferShadowed'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_buildEdgeList"
  buildEdgeList'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_freeEdgeList"
  freeEdgeList'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_prepareForShadowVolume"
  prepareForShadowVolume'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_isPreparedForShadowVolumes"
  isPreparedForShadowVolumes'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_isEdgeListBuilt"
  isEdgeListBuilt'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_setAutoBuildEdgeLists"
  setAutoBuildEdgeLists'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getAutoBuildEdgeLists"
  getAutoBuildEdgeLists'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getSharedVertexDataAnimationType"
  getSharedVertexDataAnimationType'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getSharedVertexDataAnimationIncludesNormals"
  getSharedVertexDataAnimationIncludesNormals'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_createAnimation"
  createAnimation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CFloat -> ((HG3DClassPtr) -> (IO ())))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getAnimation"
  getAnimation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_hasAnimation"
  hasAnimation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_removeAnimation"
  removeAnimation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getNumAnimations"
  getNumAnimations'_ :: ((HG3DClassPtr) -> ((Ptr CUShort) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getAnimation2"
  getAnimation2'_ :: ((HG3DClassPtr) -> (CUShort -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_removeAllAnimations"
  removeAllAnimations'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_updateMaterialForAllSubMeshes"
  updateMaterialForAllSubMeshes'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_getPoseCount"
  getPoseCount'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_removePose2"
  removePose2'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMesh.chs.h ogre_msh_removeAllPoses"
  removeAllPoses'_ :: ((HG3DClassPtr) -> (IO ()))