-- 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, 2012 Peter Althainz -- -- 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 40 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.ClassPtr {-# LINE 41 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.StructHG3DClass {-# LINE 42 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.StructVec3 {-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.StructColour {-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.EnumBillboardOrigin {-# LINE 45 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.EnumBillboardRotationType {-# LINE 46 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.StructSharedPtr {-# LINE 47 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} import HGamer3D.Bindings.Ogre.EnumBillboardType {-# LINE 48 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Usual constructor - this is called by the SceneManagerBillboardSet::setAutoextend new :: String -- ^ name - The name to give the billboard set (must be unique) -> Int -- ^ poolSize - The initial size of the billboard pool. Estimate of the number of billboards which will be required, and pass it using this parameter. The set will preallocate this number to avoid memory fragmentation. The default behaviour once this pool has run out is to double it. -> Bool -- ^ externalDataSource - If true, the source of data for drawing the billboards will not be the internal billboard list, but external data. When driving the billboard from external data, you must call _notifyCurrentCamera to reorient the billboards, setPoolSize to set the maximum billboards you want to use, beginBillboards to start the update, and injectBillboard per billboard, followed by endBillboards. -> 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 56 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | delete :: HG3DClass -- ^ classpointer - pointer of Class instance which is going to be deleted. -> IO () -- ^ delete a1 = withHG3DClass a1 $ \a1' -> delete'_ a1' >>= \res -> return () {-# LINE 60 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Creates a new billboard and adds it to this set. Behaviour once the billboard pool has been exhausted depends on the BillboardSet::setAutoextendPool option. On failiure (i.e. no more space and can't autoextend), NULLBillboardSet::setAutoextend createBillboard :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Vec3 -- ^ position - The position of the new billboard realtive to the certer of the set -> Colour -- ^ colour - Optional base colour of the billboard. -> IO (HG3DClass) -- ^ return value - On success, a pointer to a newly created 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 67 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Creates a new billboard and adds it to this set. Behaviour once the billboard pool has been exhausted depends on the BillboardSet::setAutoextendPool option. On failure (i.e. no more space and can't autoextend), NULLBillboardSet::setAutoextend createBillboard2 :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Float -- ^ x -> Float -- ^ y -> Float -- ^ z - The position of the new billboard relative to the center of the set -> Colour -- ^ colour - Optional base colour of the billboard. -> IO (HG3DClass) -- ^ return value - On success, a pointer to a newly created 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 76 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Returns the number of active billboards which currently make up this set. getNumBillboards :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ getNumBillboards a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getNumBillboards'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 81 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Tells the set whether to allow automatic extension of the pool of billboards. A BillboardSetThe default behaviour is to allow the pool to extend (typically this allocates double the current pool of billboards when the pool is expended), equivalent to calling this method with autoExtend = true. If you set the parameter to false however, any attempt to create a new billboard when the pool has expired will simply fail silently, returning a null pointer. setAutoextend :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ autoextend - true to double the pool every time it runs out, false to fail silently. -> IO () -- ^ setAutoextend a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setAutoextend'_ a1' a2' >>= \res -> return () {-# LINE 86 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Returns true if the billboard pool automatically extends. BillboardSet::setAutoextend getAutoextend :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ getAutoextend a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getAutoextend'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 91 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Enables sorting for this BillboardSet setSortingEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ sortenable - true to sort the billboards according to their distance to the camera -> IO () -- ^ setSortingEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setSortingEnabled'_ a1' a2' >>= \res -> return () {-# LINE 96 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Returns true if sorting of billboards is enabled based on their distance from the camera BillboardSet::setSortingEnabled getSortingEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ getSortingEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getSortingEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 101 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Adjusts the size of the pool of billboards available in this set. See the BillboardSet::setAutoextend setPoolSize :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ size - The new size for the pool. -> IO () -- ^ setPoolSize a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setPoolSize'_ a1' a2' >>= \res -> return () {-# LINE 106 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Returns the current size of the billboard pool. BillboardSet::setAutoextend getPoolSize :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ return value - The current size of the billboard pool. getPoolSize a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getPoolSize'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 111 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Empties this set of all billboards. clear :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ clear a1 = withHG3DClass a1 $ \a1' -> clear'_ a1' >>= \res -> return () {-# LINE 115 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Returns a pointer to the billboard at the supplied index. This method requires linear time since the billboard list is a linked list. On failure, NULL getBillboard :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ index - The index of the billboard that is requested. -> IO (HG3DClass) -- ^ return value - On success, a valid pointer to the requested billboard is returned. getBillboard a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in alloca $ \a3' -> getBillboard'_ a1' a2' a3' >>= \res -> peek a3'>>= \a3'' -> return (a3'') {-# LINE 121 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Removes the billboard at the supplied index. This method requires linear time since the billboard list is a linked list. removeBillboard :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ index -> IO () -- ^ removeBillboard a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in removeBillboard'_ a1' a2' >>= \res -> return () {-# LINE 126 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Removes a billboard from the set. This version is more efficient than removing by index. removeBillboard2 :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ pBill -> IO () -- ^ removeBillboard2 a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> removeBillboard2'_ a1' a2' >>= \res -> return () {-# LINE 131 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets the point which acts as the origin point for all billboards in this set. This setting controls the fine tuning of where a billboard appears in relation to it's position. It could be that a billboard's position represents it's center (e.g. for fireballs), it could mean the center of the bottom edge (e.g. a tree which is positioned on the ground), the top-left corner (e.g. a cursor). The default setting is BBO_CENTER. setBillboardOrigin :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> EnumBillboardOrigin -- ^ origin - A member of the BillboardOrigin enum specifying the origin for all the billboards in this set. -> IO () -- ^ setBillboardOrigin a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = cIntFromEnum a2} in setBillboardOrigin'_ a1' a2' >>= \res -> return () {-# LINE 136 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Gets the point which acts as the origin point for all billboards in this set. getBillboardOrigin :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (EnumBillboardOrigin) -- ^ return value - A member of the BillboardOrigin enum specifying the origin for all the billboards in this set. getBillboardOrigin a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getBillboardOrigin'_ a1' a2' >>= \res -> peekEnumUtil a2'>>= \a2'' -> return (a2'') {-# LINE 141 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets billboard rotation type. This setting controls the billboard rotation type, you can deciding rotate the billboard's vertices around their facing direction or rotate the billboard's texture coordinates. The default settings is BBR_TEXCOORD. setBillboardRotationType :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> EnumBillboardRotationType -- ^ rotationType - A member of the BillboardRotationType enum specifying the rotation type for all the billboards in this set. -> IO () -- ^ setBillboardRotationType a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = cIntFromEnum a2} in setBillboardRotationType'_ a1' a2' >>= \res -> return () {-# LINE 146 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets billboard rotation type. getBillboardRotationType :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (EnumBillboardRotationType) -- ^ return value - A member of the BillboardRotationType enum specifying the rotation type for all the billboards in this set. getBillboardRotationType a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getBillboardRotationType'_ a1' a2' >>= \res -> peekEnumUtil a2'>>= \a2'' -> return (a2'') {-# LINE 151 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets the default dimensions of the billboards in this set. All billboards in a set are created with these default dimensions. The set will render most efficiently if all the billboards in the set are the default size. It is possible to alter the size of individual billboards at the expense of extra calculation. See the Billboard setDefaultDimensions :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Float -- ^ width - The new default width for the billboards in this set. -> Float -- ^ height - The new default height for the billboards in this set. -> 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 157 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | See setDefaultDimensions - this sets 1 component individually. setDefaultWidth :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Float -- ^ width -> IO () -- ^ setDefaultWidth a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in setDefaultWidth'_ a1' a2' >>= \res -> return () {-# LINE 162 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | See setDefaultDimensions - this gets 1 component individually. getDefaultWidth :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Float) -- ^ getDefaultWidth a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getDefaultWidth'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 167 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | See setDefaultDimensions - this sets 1 component individually. setDefaultHeight :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Float -- ^ height -> IO () -- ^ setDefaultHeight a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in setDefaultHeight'_ a1' a2' >>= \res -> return () {-# LINE 172 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | See setDefaultDimensions - this gets 1 component individually. getDefaultHeight :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Float) -- ^ getDefaultHeight a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getDefaultHeight'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 177 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets the name of the material to be used for this billboard set. setMaterialName :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> String -- ^ name - The new name of the material to use for this set. -> String -- ^ groupName -> IO () -- ^ setMaterialName a1 a2 a3 = withHG3DClass a1 $ \a1' -> withCString a2 $ \a2' -> withCString a3 $ \a3' -> setMaterialName'_ a1' a2' a3' >>= \res -> return () {-# LINE 183 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets the name of the material to be used for this billboard set. getMaterialName :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (String) -- ^ return value - The name of the material that is used for this set. getMaterialName a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getMaterialName'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 188 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Begin injection of billboard data; applicable when constructing the BillboardSet beginBillboards :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ numBillboards - If you know the number of billboards you will be issuing, state it here to make the update more efficient. -> IO () -- ^ beginBillboards a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in beginBillboards'_ a1' a2' >>= \res -> return () {-# LINE 193 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Define a billboard. injectBillboard :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ bb -> IO () -- ^ injectBillboard a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> injectBillboard'_ a1' a2' >>= \res -> return () {-# LINE 198 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Finish defining billboards. endBillboards :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ endBillboards a1 = withHG3DClass a1 $ \a1' -> endBillboards'_ a1' >>= \res -> return () {-# LINE 202 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Overridden from MovableObjectMovableObject getBoundingRadius :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Float) -- ^ getBoundingRadius a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getBoundingRadius'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 207 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Overridden from MovableObjectMovableObject getMaterial :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (SharedPtr) -- ^ getMaterial a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getMaterial'_ a1' a2' >>= \res -> peekSharedPtr a2'>>= \a2'' -> return (a2'') {-# LINE 212 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets the name of the material to be used for this billboard set. setMaterial :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> SharedPtr -- ^ material - The new material to use for this set. -> IO () -- ^ setMaterial a1 a2 = withHG3DClass a1 $ \a1' -> withSharedPtr a2 $ \a2' -> setMaterial'_ a1' a2' >>= \res -> return () {-# LINE 217 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Returns whether or not billboards in this are tested individually for culling. getCullIndividually :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ getCullIndividually a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getCullIndividually'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 222 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets whether culling tests billboards in this individually as well as in a group. BillboardThis is useful when you have a large, fairly distributed set of billboards, like maybe trees on a landscape. You probably still want to group them into more than one set (maybe one set per section of landscape), which will be culled coarsely, but you also want to cull the billboards individually because they are spread out. Whilst you could have lots of single-tree sets which are culled separately, this would be inefficient to render because each tree would be issued as it's own rendering operation. By calling this method with a parameter of true, you can have large billboard sets which are spaced out and so get the benefit of batch rendering and coarse culling, but also have fine-grained culling so unnecessary rendering is avoided. setCullIndividually :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ cullIndividual - If true, each billboard is tested before being sent to the pipeline as well as the whole set having to pass the coarse group bounding test. -> IO () -- ^ setCullIndividually a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setCullIndividually'_ a1' a2' >>= \res -> return () {-# LINE 227 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets the type of billboard to render. The default sort of billboard (BBT_POINT), always has both x and y axes parallel to the camera's local axes. This is fine for 'point' style billboards (e.g. flares, smoke, anything which is symmetrical about a central point) but does not look good for billboards which have an orientation (e.g. an elongated raindrop). In this case, the oriented billboards are more suitable (BBT_ORIENTED_COMMON or BBT_ORIENTED_SELF) since they retain an independant Y axis and only the X axis is generated, perpendicular to both the local Y and the camera Z. In some case you might want the billboard has fixed Z axis and doesn't need to face to camera (e.g. an aureola around the player and parallel to the ground). You can use BBT_PERPENDICULAR_SELF which the billboard plane perpendicular to the billboard own direction. Or BBT_PERPENDICULAR_COMMON which the billboard plane perpendicular to the common direction. BBT_PERPENDICULAR_SELF and BBT_PERPENDICULAR_COMMON can't guarantee counterclockwise, you might use double-side material (cull_hardware node setBillboardType :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> EnumBillboardType -- ^ bbt - The type of billboard to render -> IO () -- ^ setBillboardType a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = cIntFromEnum a2} in setBillboardType'_ a1' a2' >>= \res -> return () {-# LINE 232 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Returns the billboard type in use. getBillboardType :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (EnumBillboardType) -- ^ getBillboardType a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getBillboardType'_ a1' a2' >>= \res -> peekEnumUtil a2'>>= \a2'' -> return (a2'') {-# LINE 237 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Use this to specify the common direction given to billboards of type BBT_ORIENTED_COMMON or BBT_PERPENDICULAR_COMMON. Use BBT_ORIENTED_COMMON when you want oriented billboards but you know they are always going to be oriented the same way (e.g. rain in calm weather). It is faster for the system to calculate the billboard vertices if they have a common direction. The common direction also use in BBT_PERPENDICULAR_COMMON, in this case the common direction treat as Z axis, and an additional common up-vector was use to determine billboard X and Y axis. setCommonUpVectorThe direction are use as is, never normalised in internal, user are supposed to normalise it himself. setCommonDirection :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Vec3 -- ^ vec - The direction for all billboards. -> IO () -- ^ setCommonDirection a1 a2 = withHG3DClass a1 $ \a1' -> withVec3 a2 $ \a2' -> setCommonDirection'_ a1' a2' >>= \res -> return () {-# LINE 242 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Gets the common direction for all billboards (BBT_ORIENTED_COMMON) getCommonDirection :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Vec3) -- ^ getCommonDirection a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getCommonDirection'_ a1' a2' >>= \res -> peekVec3 a2'>>= \a2'' -> return (a2'') {-# LINE 247 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Use this to specify the common up-vector given to billboards of type BBT_PERPENDICULAR_SELF or BBT_PERPENDICULAR_COMMON. Use BBT_PERPENDICULAR_SELF or BBT_PERPENDICULAR_COMMON when you want oriented billboards perpendicular to specify direction vector (or, Z axis), and doesn't face to camera. In this case, we need an additional up-vector to determine the billboard X and Y axis. The generated billboard plane and X-axis guarantee perpendicular to specify direction. setCommonDirectionThe specify direction is billboard own direction when billboard type is BBT_PERPENDICULAR_SELF, and it's shared common direction when billboard type is BBT_PERPENDICULAR_COMMON. The up-vector are use as is, never normalised in internal, user are supposed to normalise it himself. setCommonUpVector :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Vec3 -- ^ vec - The up-vector for all billboards. -> IO () -- ^ setCommonUpVector a1 a2 = withHG3DClass a1 $ \a1' -> withVec3 a2 $ \a2' -> setCommonUpVector'_ a1' a2' >>= \res -> return () {-# LINE 252 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Gets the common up-vector for all billboards (BBT_PERPENDICULAR_SELF and BBT_PERPENDICULAR_COMMON) getCommonUpVector :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Vec3) -- ^ getCommonUpVector a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getCommonUpVector'_ a1' a2' >>= \res -> peekVec3 a2'>>= \a2'' -> return (a2'') {-# LINE 257 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets whether or not billboards should use an 'accurate' facing model based on the vector from each billboard to the camera, rather than an optimised version using just the camera direction. By default, the axes for all billboards are calculated using the camera's view direction, not the vector from the camera position to the billboard. The former is faster, and most of the time the difference is not noticeable. However for some purposes (e.g. very large, static billboards) the changing billboard orientation when rotating the camera can be off putting, therefore you can enable this option to use a more expensive, but more accurate version. setUseAccurateFacing :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ acc - True to use the slower but more accurate model. Default is false. -> IO () -- ^ setUseAccurateFacing a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setUseAccurateFacing'_ a1' a2' >>= \res -> return () {-# LINE 262 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Gets whether or not billboards use an 'accurate' facing model based on the vector from each billboard to the camera, rather than an optimised version using just the camera direction. getUseAccurateFacing :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ getUseAccurateFacing a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getUseAccurateFacing'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 267 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Overridden from MovableObject getMovableType :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (String) -- ^ getMovableType a1 = withHG3DClass a1 $ \a1' -> alloc64k $ \a2' -> getMovableType'_ a1' a2' >>= \res -> peekCString a2'>>= \a2'' -> return (a2'') {-# LINE 272 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Overridden, see Renderable getSquaredViewDepth :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> HG3DClass -- ^ cam -> IO (Float) -- ^ getSquaredViewDepth a1 a2 = withHG3DClass a1 $ \a1' -> withHG3DClass a2 $ \a2' -> alloca $ \a3' -> getSquaredViewDepth'_ a1' a2' a3' >>= \res -> peekFloatConv a3'>>= \a3'' -> return (a3'') {-# LINE 278 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Sets whether billboards should be treated as being in world space. This is most useful when you are driving the billboard set from an external data source. setBillboardsInWorldSpace :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ ws -> IO () -- ^ setBillboardsInWorldSpace a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setBillboardsInWorldSpace'_ a1' a2' >>= \res -> return () {-# LINE 283 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Set whether or not the BillboardSetBy default a billboardset is rendered by generating geometry for a textured quad in memory, taking into account the size and orientation settings, and uploading it to the video card. The alternative is to use hardware point rendering, which means that only one position needs to be sent per billboard rather than 4 and the hardware sorts out how this is rendered based on the render state. Using point rendering is faster than generating quads manually, but is more restrictive. The following restrictions apply: -- -- -- -- -- -- --You will almost certainly want to enable in your material pass both point attenuation and point sprites if you use this option. setPointRenderingEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ enabled - True to enable point rendering, false otherwise -> IO () -- ^ setPointRenderingEnabled a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setPointRenderingEnabled'_ a1' a2' >>= \res -> return () {-# LINE 288 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Returns whether point rendering is enabled. isPointRenderingEnabled :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isPointRenderingEnabled a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isPointRenderingEnabled'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 293 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Override to return specific type flag. getTypeFlags :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ getTypeFlags a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getTypeFlags'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 298 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Set the auto update state of this billboard set. This methods controls the updating policy of the vertex buffer. By default auto update is true so the vertex buffer is being update every time this billboard set is about to be rendered. This behavior best fit when the billboards of this set changes frequently. When using static or semi-static billboards, it is recommended to set auto update to false. In that case one should call notifyBillboardDataChanged method to reflect changes made to the billboards data. setAutoUpdate :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Bool -- ^ autoUpdate -> IO () -- ^ setAutoUpdate a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromBool a2} in setAutoUpdate'_ a1' a2' >>= \res -> return () {-# LINE 303 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | Return the auto update state of this billboard set. getAutoUpdate :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ getAutoUpdate a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getAutoUpdate'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 308 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboardSet.chs" #-} -- | When billboard set is not auto updating its GPU buffer, the user is responsible to inform it about any billboard changes in order to reflect them at the rendering stage. Calling this method will cause GPU buffers update in the next render queue update. notifyBillboardDataChanged :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ notifyBillboardDataChanged a1 = withHG3DClass a1 $ \a1' -> notifyBillboardDataChanged'_ a1' >>= \res -> return () {-# LINE 312 ".\\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 ()))