-- 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\\ClassBillboardSet.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. -- -- ClassBillboardSet.chs -- module HGamer3D.Bindings.Ogre.ClassBillboardSet 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\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.ClassPtr {-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.StructHG3DClass {-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.StructVec3 {-# LINE 45 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.StructColour {-# LINE 46 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.EnumBillboardOrigin {-# LINE 47 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.EnumBillboardRotationType {-# LINE 48 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.StructSharedPtr {-# LINE 49 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.EnumBillboardType {-# LINE 50 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function BillboardSet2 -} new :: String -> Int -> Bool -> IO (HG3DClass) new a1 a2 a3 = withCString a1 $ \a1' -> let {a2' = fromIntegral a2} in let {a3' = fromBool a3} in alloca $ \a4' -> new'_ a1' a2' a3' a4' >>= \res -> peek a4'>>= \a4'' -> return (a4'') {-# LINE 58 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function ~BillboardSet -} delete :: HG3DClass -> IO () delete a1 = withHG3DClass a1 $ \a1' -> delete'_ a1' >>= \res -> return () {-# LINE 62 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function createBillboard -} createBillboard :: HG3DClass -> Vec3 -> Colour -> IO (HG3DClass) createBillboard a1 a2 a3 = withHG3DClass a1 $ \a1' -> withVec3 a2 $ \a2' -> withColour a3 $ \a3' -> alloca $ \a4' -> createBillboard'_ a1' a2' a3' a4' >>= \res -> peek a4'>>= \a4'' -> return (a4'') {-# LINE 69 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function createBillboard2 -} createBillboard2 :: HG3DClass -> Float -> Float -> Float -> Colour -> IO (HG3DClass) createBillboard2 a1 a2 a3 a4 a5 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in let {a3' = realToFrac a3} in let {a4' = realToFrac a4} in withColour a5 $ \a5' -> alloca $ \a6' -> createBillboard2'_ a1' a2' a3' a4' a5' a6' >>= \res -> peek a6'>>= \a6'' -> return (a6'') {-# LINE 78 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getNumBillboards -} getNumBillboards :: HG3DClass -> IO (Int) getNumBillboards a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getNumBillboards'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 83 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setAutoextend -} setAutoextend :: HG3DClass -> Bool -> IO () setAutoextend a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setAutoextend'_ a1' a2' >>= \res -> return () {-# LINE 88 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getAutoextend -} getAutoextend :: HG3DClass -> IO (Bool) getAutoextend a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getAutoextend'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 93 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setSortingEnabled -} setSortingEnabled :: HG3DClass -> Bool -> IO () setSortingEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setSortingEnabled'_ a1' a2' >>= \res -> return () {-# LINE 98 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getSortingEnabled -} getSortingEnabled :: HG3DClass -> IO (Bool) getSortingEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getSortingEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 103 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setPoolSize -} setPoolSize :: HG3DClass -> Int -> IO () setPoolSize a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setPoolSize'_ a1' a2' >>= \res -> return () {-# LINE 108 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getPoolSize -} getPoolSize :: HG3DClass -> IO (Int) getPoolSize a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getPoolSize'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 113 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function clear -} clear :: HG3DClass -> IO () clear a1 = withHG3DClass a1 $ \a1' -> clear'_ a1' >>= \res -> return () {-# LINE 117 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getBillboard -} getBillboard :: HG3DClass -> Int -> IO (HG3DClass) getBillboard a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getBillboard'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 123 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function removeBillboard -} removeBillboard :: HG3DClass -> Int -> IO () removeBillboard a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in removeBillboard'_ a1' a2' >>= \res -> return () {-# LINE 128 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function removeBillboard2 -} removeBillboard2 :: HG3DClass -> HG3DClass -> IO () removeBillboard2 a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> removeBillboard2'_ a1' a2' >>= \res -> return () {-# LINE 133 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setBillboardOrigin -} setBillboardOrigin :: HG3DClass -> EnumBillboardOrigin -> IO () setBillboardOrigin a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = cIntFromEnum a2} in setBillboardOrigin'_ a1' a2' >>= \res -> return () {-# LINE 138 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getBillboardOrigin -} getBillboardOrigin :: HG3DClass -> IO (EnumBillboardOrigin) getBillboardOrigin a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getBillboardOrigin'_ a1' a2' >>= \res -> peekEnumUtil a2'>>= \a2'' -> return (a2'') {-# LINE 143 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setBillboardRotationType -} setBillboardRotationType :: HG3DClass -> EnumBillboardRotationType -> IO () setBillboardRotationType a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = cIntFromEnum a2} in setBillboardRotationType'_ a1' a2' >>= \res -> return () {-# LINE 148 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getBillboardRotationType -} getBillboardRotationType :: HG3DClass -> IO (EnumBillboardRotationType) getBillboardRotationType a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getBillboardRotationType'_ a1' a2' >>= \res -> peekEnumUtil a2'>>= \a2'' -> return (a2'') {-# LINE 153 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setDefaultDimensions -} setDefaultDimensions :: HG3DClass -> Float -> Float -> IO () setDefaultDimensions a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in let {a3' = realToFrac a3} in setDefaultDimensions'_ a1' a2' a3' >>= \res -> return () {-# LINE 159 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setDefaultWidth -} setDefaultWidth :: HG3DClass -> Float -> IO () setDefaultWidth a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in setDefaultWidth'_ a1' a2' >>= \res -> return () {-# LINE 164 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getDefaultWidth -} getDefaultWidth :: HG3DClass -> IO (Float) getDefaultWidth a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getDefaultWidth'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 169 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setDefaultHeight -} setDefaultHeight :: HG3DClass -> Float -> IO () setDefaultHeight a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in setDefaultHeight'_ a1' a2' >>= \res -> return () {-# LINE 174 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getDefaultHeight -} getDefaultHeight :: HG3DClass -> IO (Float) getDefaultHeight a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getDefaultHeight'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 179 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.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 185 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getMaterialName -} getMaterialName :: HG3DClass -> IO (String) getMaterialName a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getMaterialName'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 190 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function beginBillboards -} beginBillboards :: HG3DClass -> Int -> IO () beginBillboards a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in beginBillboards'_ a1' a2' >>= \res -> return () {-# LINE 195 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function injectBillboard -} injectBillboard :: HG3DClass -> HG3DClass -> IO () injectBillboard a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> injectBillboard'_ a1' a2' >>= \res -> return () {-# LINE 200 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function endBillboards -} endBillboards :: HG3DClass -> IO () endBillboards a1 = withHG3DClass a1 $ \a1' -> endBillboards'_ a1' >>= \res -> return () {-# LINE 204 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getBoundingRadius -} getBoundingRadius :: HG3DClass -> IO (Float) getBoundingRadius a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getBoundingRadius'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 209 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getMaterial -} getMaterial :: HG3DClass -> IO (SharedPtr) getMaterial a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getMaterial'_ a1' a2' >>= \res -> peekSharedPtr a2'>>= \a2'' -> return (a2'') {-# LINE 214 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setMaterial -} setMaterial :: HG3DClass -> SharedPtr -> IO () setMaterial a1 a2 = withHG3DClass a1 $ \a1' -> withSharedPtr a2 $ \a2' -> setMaterial'_ a1' a2' >>= \res -> return () {-# LINE 219 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getCullIndividually -} getCullIndividually :: HG3DClass -> IO (Bool) getCullIndividually a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getCullIndividually'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 224 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setCullIndividually -} setCullIndividually :: HG3DClass -> Bool -> IO () setCullIndividually a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setCullIndividually'_ a1' a2' >>= \res -> return () {-# LINE 229 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setBillboardType -} setBillboardType :: HG3DClass -> EnumBillboardType -> IO () setBillboardType a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = cIntFromEnum a2} in setBillboardType'_ a1' a2' >>= \res -> return () {-# LINE 234 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getBillboardType -} getBillboardType :: HG3DClass -> IO (EnumBillboardType) getBillboardType a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getBillboardType'_ a1' a2' >>= \res -> peekEnumUtil a2'>>= \a2'' -> return (a2'') {-# LINE 239 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setCommonDirection -} setCommonDirection :: HG3DClass -> Vec3 -> IO () setCommonDirection a1 a2 = withHG3DClass a1 $ \a1' -> withVec3 a2 $ \a2' -> setCommonDirection'_ a1' a2' >>= \res -> return () {-# LINE 244 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getCommonDirection -} getCommonDirection :: HG3DClass -> IO (Vec3) getCommonDirection a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getCommonDirection'_ a1' a2' >>= \res -> peekVec3 a2'>>= \a2'' -> return (a2'') {-# LINE 249 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setCommonUpVector -} setCommonUpVector :: HG3DClass -> Vec3 -> IO () setCommonUpVector a1 a2 = withHG3DClass a1 $ \a1' -> withVec3 a2 $ \a2' -> setCommonUpVector'_ a1' a2' >>= \res -> return () {-# LINE 254 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getCommonUpVector -} getCommonUpVector :: HG3DClass -> IO (Vec3) getCommonUpVector a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getCommonUpVector'_ a1' a2' >>= \res -> peekVec3 a2'>>= \a2'' -> return (a2'') {-# LINE 259 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setUseAccurateFacing -} setUseAccurateFacing :: HG3DClass -> Bool -> IO () setUseAccurateFacing a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setUseAccurateFacing'_ a1' a2' >>= \res -> return () {-# LINE 264 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getUseAccurateFacing -} getUseAccurateFacing :: HG3DClass -> IO (Bool) getUseAccurateFacing a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getUseAccurateFacing'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 269 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getMovableType -} getMovableType :: HG3DClass -> IO (String) getMovableType a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getMovableType'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 274 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getSquaredViewDepth -} getSquaredViewDepth :: HG3DClass -> HG3DClass -> IO (Float) getSquaredViewDepth a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> alloca $ \a3' -> getSquaredViewDepth'_ a1' a2' a3' >>= \res -> peekFloatConv a3'>>= \a3'' -> return (a3'') {-# LINE 280 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setBillboardsInWorldSpace -} setBillboardsInWorldSpace :: HG3DClass -> Bool -> IO () setBillboardsInWorldSpace a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setBillboardsInWorldSpace'_ a1' a2' >>= \res -> return () {-# LINE 285 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setPointRenderingEnabled -} setPointRenderingEnabled :: HG3DClass -> Bool -> IO () setPointRenderingEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setPointRenderingEnabled'_ a1' a2' >>= \res -> return () {-# LINE 290 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function isPointRenderingEnabled -} isPointRenderingEnabled :: HG3DClass -> IO (Bool) isPointRenderingEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isPointRenderingEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 295 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getTypeFlags -} getTypeFlags :: HG3DClass -> IO (Int) getTypeFlags a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getTypeFlags'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 300 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function setAutoUpdate -} setAutoUpdate :: HG3DClass -> Bool -> IO () setAutoUpdate a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setAutoUpdate'_ a1' a2' >>= \res -> return () {-# LINE 305 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function getAutoUpdate -} getAutoUpdate :: HG3DClass -> IO (Bool) getAutoUpdate a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getAutoUpdate'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 310 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} {- function notifyBillboardDataChanged -} notifyBillboardDataChanged :: HG3DClass -> IO () notifyBillboardDataChanged a1 = withHG3DClass a1 $ \a1' -> notifyBillboardDataChanged'_ a1' >>= \res -> return () {-# LINE 314 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_construct" new'_ :: ((Ptr CChar) -> (CUInt -> (CInt -> ((HG3DClassPtr) -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_destruct" delete'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_createBillboard" createBillboard'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> ((ColourPtr) -> ((HG3DClassPtr) -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_createBillboard2" createBillboard2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> ((ColourPtr) -> ((HG3DClassPtr) -> (IO ()))))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getNumBillboards" getNumBillboards'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setAutoextend" setAutoextend'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getAutoextend" getAutoextend'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setSortingEnabled" setSortingEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getSortingEnabled" getSortingEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setPoolSize" setPoolSize'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getPoolSize" getPoolSize'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_clear" clear'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getBillboard" getBillboard'_ :: ((HG3DClassPtr) -> (CUInt -> ((HG3DClassPtr) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_removeBillboard" removeBillboard'_ :: ((HG3DClassPtr) -> (CUInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_removeBillboard2" removeBillboard2'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setBillboardOrigin" setBillboardOrigin'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getBillboardOrigin" getBillboardOrigin'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setBillboardRotationType" setBillboardRotationType'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getBillboardRotationType" getBillboardRotationType'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setDefaultDimensions" setDefaultDimensions'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setDefaultWidth" setDefaultWidth'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getDefaultWidth" getDefaultWidth'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setDefaultHeight" setDefaultHeight'_ :: ((HG3DClassPtr) -> (CFloat -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getDefaultHeight" getDefaultHeight'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setMaterialName" setMaterialName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> ((Ptr CChar) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getMaterialName" getMaterialName'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_beginBillboards" beginBillboards'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_injectBillboard" injectBillboard'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_endBillboards" endBillboards'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getBoundingRadius" getBoundingRadius'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getMaterial" getMaterial'_ :: ((HG3DClassPtr) -> ((SharedPtrPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setMaterial" setMaterial'_ :: ((HG3DClassPtr) -> ((SharedPtrPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getCullIndividually" getCullIndividually'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setCullIndividually" setCullIndividually'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setBillboardType" setBillboardType'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getBillboardType" getBillboardType'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setCommonDirection" setCommonDirection'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getCommonDirection" getCommonDirection'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setCommonUpVector" setCommonUpVector'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getCommonUpVector" getCommonUpVector'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setUseAccurateFacing" setUseAccurateFacing'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getUseAccurateFacing" getUseAccurateFacing'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getMovableType" getMovableType'_ :: ((HG3DClassPtr) -> ((Ptr CChar) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getSquaredViewDepth" getSquaredViewDepth'_ :: ((HG3DClassPtr) -> ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setBillboardsInWorldSpace" setBillboardsInWorldSpace'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setPointRenderingEnabled" setPointRenderingEnabled'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_isPointRenderingEnabled" isPointRenderingEnabled'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getTypeFlags" getTypeFlags'_ :: ((HG3DClassPtr) -> ((Ptr CUInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_setAutoUpdate" setAutoUpdate'_ :: ((HG3DClassPtr) -> (CInt -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_getAutoUpdate" getAutoUpdate'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs.h ogre_bbs_notifyBillboardDataChanged" notifyBillboardDataChanged'_ :: ((HG3DClassPtr) -> (IO ()))