-- 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\\ClassSceneNode.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-2013 Peter Althainz -- -- The files are part of HGamer3D (www.hgamer3d.org) -- -- 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. -- -- ClassSceneNode.chs -- module HGamer3D.Bindings.Ogre.ClassSceneNode 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 42 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} import HGamer3D.Bindings.Ogre.ClassPtr {-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} import HGamer3D.Bindings.Ogre.StructHG3DClass {-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} import HGamer3D.Bindings.Ogre.StructVec3 {-# LINE 45 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} import HGamer3D.Bindings.Ogre.StructQuaternion {-# LINE 46 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function ~SceneNode -} delete :: HG3DClass -> IO () delete a1 = withHG3DClass a1 $ \a1' -> delete'_ a1' >>= \res -> return () {-# LINE 51 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function attachObject -} attachObject :: HG3DClass -> HG3DClass -> IO () attachObject a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> attachObject'_ a1' a2' >>= \res -> return () {-# LINE 56 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function numAttachedObjects -} numAttachedObjects :: HG3DClass -> IO (Int) numAttachedObjects a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> numAttachedObjects'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 61 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function getAttachedObject -} getAttachedObject :: HG3DClass -> Int -> IO (HG3DClass) getAttachedObject a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getAttachedObject'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 67 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function getAttachedObject2 -} getAttachedObject2 :: HG3DClass -> String -> IO (HG3DClass) getAttachedObject2 a1 a2 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> alloca $ \a3' -> getAttachedObject2'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 73 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function detachObject -} detachObject :: HG3DClass -> Int -> IO (HG3DClass) detachObject a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> detachObject'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 79 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function detachObject2 -} detachObject2 :: HG3DClass -> HG3DClass -> IO () detachObject2 a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> detachObject2'_ a1' a2' >>= \res -> return () {-# LINE 84 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function detachObject3 -} detachObject3 :: HG3DClass -> String -> IO (HG3DClass) detachObject3 a1 a2 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> alloca $ \a3' -> detachObject3'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 90 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function detachAllObjects -} detachAllObjects :: HG3DClass -> IO () detachAllObjects a1 = withHG3DClass a1 $ \a1' -> detachAllObjects'_ a1' >>= \res -> return () {-# LINE 94 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function isInSceneGraph -} isInSceneGraph :: HG3DClass -> IO (Bool) isInSceneGraph a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isInSceneGraph'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 99 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function getCreator -} getCreator :: HG3DClass -> IO (HG3DClass) getCreator a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getCreator'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 104 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function removeAndDestroyChild -} removeAndDestroyChild :: HG3DClass -> String -> IO () removeAndDestroyChild a1 a2 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> removeAndDestroyChild'_ a1' a2' >>= \res -> return () {-# LINE 109 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function removeAndDestroyChild2 -} removeAndDestroyChild2 :: HG3DClass -> Int -> IO () removeAndDestroyChild2 a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in removeAndDestroyChild2'_ a1' a2' >>= \res -> return () {-# LINE 114 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function removeAndDestroyAllChildren -} removeAndDestroyAllChildren :: HG3DClass -> IO () removeAndDestroyAllChildren a1 = withHG3DClass a1 $ \a1' -> removeAndDestroyAllChildren'_ a1' >>= \res -> return () {-# LINE 118 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function showBoundingBox -} showBoundingBox :: HG3DClass -> Bool -> IO () showBoundingBox a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in showBoundingBox'_ a1' a2' >>= \res -> return () {-# LINE 123 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function hideBoundingBox -} hideBoundingBox :: HG3DClass -> Bool -> IO () hideBoundingBox a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in hideBoundingBox'_ a1' a2' >>= \res -> return () {-# LINE 128 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function getShowBoundingBox -} getShowBoundingBox :: HG3DClass -> IO (Bool) getShowBoundingBox a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getShowBoundingBox'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 133 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function createChildSceneNode -} createChildSceneNode :: HG3DClass -> Vec3 -> Quaternion -> IO (HG3DClass) createChildSceneNode a1 a2 a3 = withHG3DClass a1 $ \a1' -> withVec3 a2 $ \a2' -> withQuaternion a3 $ \a3' -> alloca $ \a4' -> createChildSceneNode'_ a1' a2' a3' a4' >>= \res -> peek a4'>>= \a4'' -> return (a4'') {-# LINE 140 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function createChildSceneNode2 -} createChildSceneNode2 :: HG3DClass -> String -> Vec3 -> Quaternion -> IO (HG3DClass) createChildSceneNode2 a1 a2 a3 a4 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> withVec3 a3 $ \a3' -> withQuaternion a4 $ \a4' -> alloca $ \a5' -> createChildSceneNode2'_ a1' a2' a3' a4' a5' >>= \res -> peek a5'>>= \a5'' -> return (a5'') {-# LINE 148 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function setFixedYawAxis -} setFixedYawAxis :: HG3DClass -> Bool -> Vec3 -> IO () setFixedYawAxis a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in withVec3 a3 $ \a3' -> setFixedYawAxis'_ a1' a2' a3' >>= \res -> return () {-# LINE 154 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function getAutoTrackTarget -} getAutoTrackTarget :: HG3DClass -> IO (HG3DClass) getAutoTrackTarget a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getAutoTrackTarget'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 159 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function getAutoTrackOffset -} getAutoTrackOffset :: HG3DClass -> IO (Vec3) getAutoTrackOffset a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getAutoTrackOffset'_ a1' a2' >>= \res -> peekVec3 a2'>>= \a2'' -> return (a2'') {-# LINE 164 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function getAutoTrackLocalDirection -} getAutoTrackLocalDirection :: HG3DClass -> IO (Vec3) getAutoTrackLocalDirection a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getAutoTrackLocalDirection'_ a1' a2' >>= \res -> peekVec3 a2'>>= \a2'' -> return (a2'') {-# LINE 169 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function getParentSceneNode -} getParentSceneNode :: HG3DClass -> IO (HG3DClass) getParentSceneNode a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getParentSceneNode'_ a1' a2' >>= \res -> peek a2'>>= \a2'' -> return (a2'') {-# LINE 174 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function setVisible -} setVisible :: HG3DClass -> Bool -> Bool -> IO () setVisible a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in let {a3' = fromBool a3} in setVisible'_ a1' a2' a3' >>= \res -> return () {-# LINE 180 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function flipVisibility -} flipVisibility :: HG3DClass -> Bool -> IO () flipVisibility a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in flipVisibility'_ a1' a2' >>= \res -> return () {-# LINE 185 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} {- function setDebugDisplayEnabled -} setDebugDisplayEnabled :: HG3DClass -> Bool -> Bool -> IO () setDebugDisplayEnabled a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in let {a3' = fromBool a3} in setDebugDisplayEnabled'_ a1' a2' a3' >>= \res -> return () {-# LINE 191 ".\\HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs" #-} foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_destruct" delete'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_attachObject" attachObject'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_numAttachedObjects" numAttachedObjects'_ :: ((HG3DClassPtr) -> ((Ptr CUShort) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_getAttachedObject" getAttachedObject'_ :: ((HG3DClassPtr) -> (CUShort -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_getAttachedObject2" getAttachedObject2'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_detachObject" detachObject'_ :: ((HG3DClassPtr) -> (CUShort -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_detachObject2" detachObject2'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_detachObject3" detachObject3'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_detachAllObjects" detachAllObjects'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_isInSceneGraph" isInSceneGraph'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_getCreator" getCreator'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_removeAndDestroyChild" removeAndDestroyChild'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_removeAndDestroyChild2" removeAndDestroyChild2'_ :: ((HG3DClassPtr) -> (CUShort -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_removeAndDestroyAllChildren" removeAndDestroyAllChildren'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_showBoundingBox" showBoundingBox'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_hideBoundingBox" hideBoundingBox'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_getShowBoundingBox" getShowBoundingBox'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_createChildSceneNode" createChildSceneNode'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> ((QuaternionPtr) -> ((HG3DClassPtr) -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_createChildSceneNode2" createChildSceneNode2'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Vec3Ptr) -> ((QuaternionPtr) -> ((HG3DClassPtr) -> (IO ())))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_setFixedYawAxis" setFixedYawAxis'_ :: ((HG3DClassPtr) -> (CInt -> ((Vec3Ptr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_getAutoTrackTarget" getAutoTrackTarget'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_getAutoTrackOffset" getAutoTrackOffset'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_getAutoTrackLocalDirection" getAutoTrackLocalDirection'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_getParentSceneNode" getParentSceneNode'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_setVisible" setVisible'_ :: ((HG3DClassPtr) -> (CInt -> (CInt -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_flipVisibility" flipVisibility'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassSceneNode.chs.h ogre_sn_setDebugDisplayEnabled" setDebugDisplayEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (CInt -> (IO ()))))