module HGamer3D.Bindings.Ogre.ClassMovableObject 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
delete :: HG3DClass -> IO ()
delete a1 =
  withHG3DClass a1 $ \a1' -> 
  delete'_ a1' >>= \res ->
  return ()
getName :: HG3DClass -> IO (String)
getName a1 =
  withHG3DClass a1 $ \a1' -> 
  alloc64k $ \a2' -> 
  getName'_ a1' a2' >>= \res ->
  peekCString  a2'>>= \a2'' -> 
  return (a2'')
getMovableType :: HG3DClass -> IO (String)
getMovableType a1 =
  withHG3DClass a1 $ \a1' -> 
  alloc64k $ \a2' -> 
  getMovableType'_ a1' a2' >>= \res ->
  peekCString  a2'>>= \a2'' -> 
  return (a2'')
getParentNode :: HG3DClass -> IO (HG3DClass)
getParentNode a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getParentNode'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
getParentSceneNode :: HG3DClass -> IO (HG3DClass)
getParentSceneNode a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getParentSceneNode'_ a1' a2' >>= \res ->
  peek  a2'>>= \a2'' -> 
  return (a2'')
isParentTagPoint :: HG3DClass -> IO (Bool)
isParentTagPoint a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isParentTagPoint'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
isAttached :: HG3DClass -> IO (Bool)
isAttached a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isAttached'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
detachFromParent :: HG3DClass -> IO ()
detachFromParent a1 =
  withHG3DClass a1 $ \a1' -> 
  detachFromParent'_ a1' >>= \res ->
  return ()
isInScene :: HG3DClass -> IO (Bool)
isInScene a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isInScene'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
getBoundingRadius :: HG3DClass -> IO (Float)
getBoundingRadius a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getBoundingRadius'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
setVisible :: HG3DClass -> Bool -> IO ()
setVisible a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setVisible'_ a1' a2' >>= \res ->
  return ()
getVisible :: HG3DClass -> IO (Bool)
getVisible a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getVisible'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
isVisible :: HG3DClass -> IO (Bool)
isVisible a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isVisible'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
setRenderingDistance :: HG3DClass -> Float -> IO ()
setRenderingDistance a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setRenderingDistance'_ a1' a2' >>= \res ->
  return ()
getRenderingDistance :: HG3DClass -> IO (Float)
getRenderingDistance a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRenderingDistance'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
setRenderingMinPixelSize :: HG3DClass -> Float -> IO ()
setRenderingMinPixelSize a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = realToFrac a2} in 
  setRenderingMinPixelSize'_ a1' a2' >>= \res ->
  return ()
getRenderingMinPixelSize :: HG3DClass -> IO (Float)
getRenderingMinPixelSize a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getRenderingMinPixelSize'_ a1' a2' >>= \res ->
  peekFloatConv  a2'>>= \a2'' -> 
  return (a2'')
setQueryFlags :: HG3DClass -> Int -> IO ()
setQueryFlags a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  setQueryFlags'_ a1' a2' >>= \res ->
  return ()
addQueryFlags :: HG3DClass -> Int -> IO ()
addQueryFlags a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  addQueryFlags'_ a1' a2' >>= \res ->
  return ()
removeQueryFlags :: HG3DClass -> Int -> IO ()
removeQueryFlags a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  removeQueryFlags'_ a1' a2' >>= \res ->
  return ()
getQueryFlags :: HG3DClass -> IO (Int)
getQueryFlags a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getQueryFlags'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
setVisibilityFlags :: HG3DClass -> Int -> IO ()
setVisibilityFlags a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  setVisibilityFlags'_ a1' a2' >>= \res ->
  return ()
addVisibilityFlags :: HG3DClass -> Int -> IO ()
addVisibilityFlags a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  addVisibilityFlags'_ a1' a2' >>= \res ->
  return ()
removeVisibilityFlags :: HG3DClass -> Int -> IO ()
removeVisibilityFlags a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  removeVisibilityFlags'_ a1' a2' >>= \res ->
  return ()
getVisibilityFlags :: HG3DClass -> IO (Int)
getVisibilityFlags a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getVisibilityFlags'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
getLightMask :: HG3DClass -> IO (Int)
getLightMask a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getLightMask'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
setLightMask :: HG3DClass -> Int -> IO ()
setLightMask a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromIntegral a2} in 
  setLightMask'_ a1' a2' >>= \res ->
  return ()
hasEdgeList :: HG3DClass -> IO (Bool)
hasEdgeList a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  hasEdgeList'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
setCastShadows :: HG3DClass -> Bool -> IO ()
setCastShadows a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setCastShadows'_ a1' a2' >>= \res ->
  return ()
getCastShadows :: HG3DClass -> IO (Bool)
getCastShadows a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getCastShadows'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
getReceivesShadows :: HG3DClass -> IO (Bool)
getReceivesShadows a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getReceivesShadows'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
getPointExtrusionDistance :: HG3DClass -> HG3DClass -> IO (Float)
getPointExtrusionDistance a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  withHG3DClass a2 $ \a2' -> 
  alloca $ \a3' -> 
  getPointExtrusionDistance'_ a1' a2' a3' >>= \res ->
  peekFloatConv  a3'>>= \a3'' -> 
  return (a3'')
getTypeFlags :: HG3DClass -> IO (Int)
getTypeFlags a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  getTypeFlags'_ a1' a2' >>= \res ->
  peekIntConv  a2'>>= \a2'' -> 
  return (a2'')
setDebugDisplayEnabled :: HG3DClass -> Bool -> IO ()
setDebugDisplayEnabled a1 a2 =
  withHG3DClass a1 $ \a1' -> 
  let {a2' = fromBool a2} in 
  setDebugDisplayEnabled'_ a1' a2' >>= \res ->
  return ()
isDebugDisplayEnabled :: HG3DClass -> IO (Bool)
isDebugDisplayEnabled a1 =
  withHG3DClass a1 $ \a1' -> 
  alloca $ \a2' -> 
  isDebugDisplayEnabled'_ a1' a2' >>= \res ->
  peekBoolUtil  a2'>>= \a2'' -> 
  return (a2'')
setDefaultQueryFlags :: Int -> IO ()
setDefaultQueryFlags a1 =
  let {a1' = fromIntegral a1} in 
  setDefaultQueryFlags'_ a1' >>= \res ->
  return ()
getDefaultQueryFlags :: IO (Int)
getDefaultQueryFlags =
  alloca $ \a1' -> 
  getDefaultQueryFlags'_ a1' >>= \res ->
  peekIntConv  a1'>>= \a1'' -> 
  return (a1'')
setDefaultVisibilityFlags :: Int -> IO ()
setDefaultVisibilityFlags a1 =
  let {a1' = fromIntegral a1} in 
  setDefaultVisibilityFlags'_ a1' >>= \res ->
  return ()
getDefaultVisibilityFlags :: IO (Int)
getDefaultVisibilityFlags =
  alloca $ \a1' -> 
  getDefaultVisibilityFlags'_ a1' >>= \res ->
  peekIntConv  a1'>>= \a1'' -> 
  return (a1'')
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_destruct"
  delete'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getName"
  getName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getMovableType"
  getMovableType'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getParentNode"
  getParentNode'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getParentSceneNode"
  getParentSceneNode'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_isParentTagPoint"
  isParentTagPoint'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_isAttached"
  isAttached'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_detachFromParent"
  detachFromParent'_ :: ((HG3DClassPtr) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_isInScene"
  isInScene'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getBoundingRadius"
  getBoundingRadius'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_setVisible"
  setVisible'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getVisible"
  getVisible'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_isVisible"
  isVisible'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_setRenderingDistance"
  setRenderingDistance'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getRenderingDistance"
  getRenderingDistance'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_setRenderingMinPixelSize"
  setRenderingMinPixelSize'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getRenderingMinPixelSize"
  getRenderingMinPixelSize'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_setQueryFlags"
  setQueryFlags'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_addQueryFlags"
  addQueryFlags'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_removeQueryFlags"
  removeQueryFlags'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getQueryFlags"
  getQueryFlags'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_setVisibilityFlags"
  setVisibilityFlags'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_addVisibilityFlags"
  addVisibilityFlags'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_removeVisibilityFlags"
  removeVisibilityFlags'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getVisibilityFlags"
  getVisibilityFlags'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getLightMask"
  getLightMask'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_setLightMask"
  setLightMask'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_hasEdgeList"
  hasEdgeList'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_setCastShadows"
  setCastShadows'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getCastShadows"
  getCastShadows'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getReceivesShadows"
  getReceivesShadows'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getPointExtrusionDistance"
  getPointExtrusionDistance'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getTypeFlags"
  getTypeFlags'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_setDebugDisplayEnabled"
  setDebugDisplayEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_isDebugDisplayEnabled"
  isDebugDisplayEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ())))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_setDefaultQueryFlags"
  setDefaultQueryFlags'_ :: (CUInt -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getDefaultQueryFlags"
  getDefaultQueryFlags'_ :: ((Ptr CUInt) -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_setDefaultVisibilityFlags"
  setDefaultVisibilityFlags'_ :: (CUInt -> (IO ()))
foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassMovableObject.chs.h ogre_mvo_getDefaultVisibilityFlags"
  getDefaultVisibilityFlags'_ :: ((Ptr CUInt) -> (IO ()))