module HGamer3D.Bindings.Ogre.ClassSkeleton 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.EnumSkeletonAnimationBlendMode
delete :: HG3DClass -> IO ()
delete a1 =
  withHG3DClass a1 $ \a1' -> 
  delete'_ a1' >>= \res ->
  return ()
createBone :: HG3DClass -> IO (HG3DClass)
createBone a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  createBone'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
createBone2 :: HG3DClass -> Int -> IO (HG3DClass)
createBone2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  createBone2'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
createBone3 :: HG3DClass -> String -> IO (HG3DClass)
createBone3 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  createBone3'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
createBone4 :: HG3DClass -> String -> Int -> IO (HG3DClass)
createBone4 a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  let {a3' = fromIntegral a3} in 
  alloca $ \a4' -> 
  createBone4'_ a1' a2' a3' a4' >>= \res ->
  peek  a4'>>= \a4'' -> 
  return (a4'')
getNumBones :: HG3DClass -> IO (Int)
getNumBones a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getNumBones'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
getRootBone :: HG3DClass -> IO (HG3DClass)
getRootBone a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRootBone'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
getBone :: HG3DClass -> Int -> IO (HG3DClass)
getBone a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getBone'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
getBone2 :: HG3DClass -> String -> IO (HG3DClass)
getBone2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  getBone2'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
hasBone :: HG3DClass -> String -> IO (Bool)
hasBone a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  hasBone'_ a1' a2' a3' >>= \res ->
  peekBoolUtil  a3'>>= \a3'' -> 
  return (a3'')
setBindingPose :: HG3DClass -> IO ()
setBindingPose a1 =
  withHG3DClass a1 $ \a1' -> 
  setBindingPose'_ a1' >>= \res ->
  return ()
reset :: HG3DClass -> Bool -> IO ()
reset a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  reset'_ a1' a2' >>= \res ->
  return ()
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'')
getAnimation2 :: HG3DClass -> String -> IO (HG3DClass)
getAnimation2 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  alloca $ \a3' -> 
  getAnimation2'_ 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 ()
setAnimationState :: HG3DClass -> HG3DClass -> IO ()
setAnimationState a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  setAnimationState'_ a1' a2' >>= \res ->
  return ()
getNumAnimations :: HG3DClass -> IO (Int)
getNumAnimations a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getNumAnimations'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
getAnimation3 :: HG3DClass -> Int -> IO (HG3DClass)
getAnimation3 a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  alloca $ \a3' -> 
  getAnimation3'_ a1' a2' a3' >>= \res ->
  peek  a3'>>= \a3'' -> 
  return (a3'')
getBlendMode :: HG3DClass -> IO (EnumSkeletonAnimationBlendMode)
getBlendMode a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getBlendMode'_ a1' a2' >>= \res ->
  peekEnumUtil  a2'>>= \a2'' -> 
  return (a2'')
setBlendMode :: HG3DClass -> EnumSkeletonAnimationBlendMode -> IO ()
setBlendMode a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = cIntFromEnum a2} in 
  setBlendMode'_ a1' a2' >>= \res ->
  return ()
optimiseAllAnimations :: HG3DClass -> Bool -> IO ()
optimiseAllAnimations a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  optimiseAllAnimations'_ a1' a2' >>= \res ->
  return ()
addLinkedSkeletonAnimationSource :: HG3DClass -> String -> Float -> IO ()
addLinkedSkeletonAnimationSource a1 a2 a3 =
  withHG3DClass a1 $ \a1' -> 
  withCString a2 $ \a2' -> 
  let {a3' = realToFrac a3} in 
  addLinkedSkeletonAnimationSource'_ a1' a2' a3' >>= \res ->
  return ()
removeAllLinkedSkeletonAnimationSources :: HG3DClass -> IO ()
removeAllLinkedSkeletonAnimationSources a1 =
  withHG3DClass a1 $ \a1' -> 
  removeAllLinkedSkeletonAnimationSources'_ a1' >>= \res ->
  return ()
getManualBonesDirty :: HG3DClass -> IO (Bool)
getManualBonesDirty a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getManualBonesDirty'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
hasManualBones :: HG3DClass -> IO (Bool)
hasManualBones a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  hasManualBones'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_destruct"
  delete'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_createBone"
  createBone'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_createBone2"
  createBone2'_ :: ((HG3DClassPtr) -> (CUShort -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_createBone3"
  createBone3'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_createBone4"
  createBone4'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CUShort -> ((HG3DClassPtr) -> (IO ())))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_getNumBones"
  getNumBones'_ :: ((HG3DClassPtr) -> ((Ptr CUShort) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_getRootBone"
  getRootBone'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_getBone"
  getBone'_ :: ((HG3DClassPtr) -> (CUShort -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_getBone2"
  getBone2'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_hasBone"
  hasBone'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_setBindingPose"
  setBindingPose'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_reset"
  reset'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_createAnimation"
  createAnimation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CFloat -> ((HG3DClassPtr) -> (IO ())))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_getAnimation2"
  getAnimation2'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_hasAnimation"
  hasAnimation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_removeAnimation"
  removeAnimation'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_setAnimationState"
  setAnimationState'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_getNumAnimations"
  getNumAnimations'_ :: ((HG3DClassPtr) -> ((Ptr CUShort) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_getAnimation3"
  getAnimation3'_ :: ((HG3DClassPtr) -> (CUShort -> ((HG3DClassPtr) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_getBlendMode"
  getBlendMode'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_setBlendMode"
  setBlendMode'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_optimiseAllAnimations"
  optimiseAllAnimations'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_addLinkedSkeletonAnimationSource"
  addLinkedSkeletonAnimationSource'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (CFloat -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_removeAllLinkedSkeletonAnimationSources"
  removeAllLinkedSkeletonAnimationSources'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_getManualBonesDirty"
  getManualBonesDirty'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSkeleton.chs.h ogre_skl_hasManualBones"
  hasManualBones'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))