-- 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\\ClassBillboard.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. -- -- ClassBillboard.chs -- module HGamer3D.Bindings.Ogre.ClassBillboard where import C2HS import Foreign import Foreign.Ptr import Foreign.C import Monad (liftM, liftM2) 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\\ClassBillboard.chs" #-} import HGamer3D.Bindings.Ogre.ClassPtr {-# LINE 43 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} import HGamer3D.Bindings.Ogre.StructHG3DClass {-# LINE 44 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} import HGamer3D.Bindings.Ogre.StructRadians {-# LINE 45 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} import HGamer3D.Bindings.Ogre.StructVec3 {-# LINE 46 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} import HGamer3D.Bindings.Ogre.StructColour {-# LINE 47 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Default constructor. new :: IO (HG3DClass) -- ^ new = alloca $ \a1' -> new'_ a1' >>= \res -> peek a1'>>= \a1'' -> return (a1'') {-# LINE 52 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Default destructor. delete :: HG3DClass -- ^ classpointer - pointer of Class instance which is going to be deleted. -> IO () -- ^ delete a1 = withHG3DClass a1 $ \a1' -> delete'_ a1' >>= \res -> return () {-# LINE 56 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Get the rotation of the billboard. This rotation is relative to the center of the billboard. getRotation :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Radians) -- ^ getRotation a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getRotation'_ a1' a2' >>= \res -> peekRadians a2'>>= \a2'' -> return (a2'') {-# LINE 61 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Set the rotation of the billboard. This rotation is relative to the center of the billboard. setRotation :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Radians -- ^ rotation -> IO () -- ^ setRotation a1 a2 = withHG3DClass a1 $ \a1' -> withRadians a2 $ \a2' -> setRotation'_ a1' a2' >>= \res -> return () {-# LINE 66 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Set the position of the billboard. This position is relative to a point on the quad which is the billboard. Depending on the BillboardSetBillboardSet::setBillboardOrigin setPosition :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Vec3 -- ^ position -> IO () -- ^ setPosition a1 a2 = withHG3DClass a1 $ \a1' -> withVec3 a2 $ \a2' -> setPosition'_ a1' a2' >>= \res -> return () {-# LINE 71 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Set the position of the billboard. This position is relative to a point on the quad which is the billboard. Depending on the BillboardSetBillboardSet::setBillboardOrigin setPosition2 :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Float -- ^ x -> Float -- ^ y -> Float -- ^ z -> IO () -- ^ setPosition2 a1 a2 a3 a4 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in let {a3' = realToFrac a3} in let {a4' = realToFrac a4} in setPosition2'_ a1' a2' a3' a4' >>= \res -> return () {-# LINE 78 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Get the position of the billboard. This position is relative to a point on the quad which is the billboard. Depending on the BillboardSetBillboardSet::setBillboardOrigin getPosition :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Vec3) -- ^ getPosition a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getPosition'_ a1' a2' >>= \res -> peekVec3 a2'>>= \a2'' -> return (a2'') {-# LINE 83 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Sets the width and height for this billboard. Note that it is most efficient for every billboard in a BillboardSetBillboardSet::setDefaultDimensions setDimensions :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Float -- ^ width -> Float -- ^ height -> IO () -- ^ setDimensions a1 a2 a3 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in let {a3' = realToFrac a3} in setDimensions'_ a1' a2' a3' >>= \res -> return () {-# LINE 89 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Resets this BillboardBillboardSet resetDimensions :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO () -- ^ resetDimensions a1 = withHG3DClass a1 $ \a1' -> resetDimensions'_ a1' >>= \res -> return () {-# LINE 93 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Sets the colour of this billboard. Billboards can be tinted based on a base colour. This allows variations in colour irrespective of the base colour of the material allowing more varied billboards. The default colour is white. The tinting is effected using vertex colours. setColour :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Colour -- ^ colour -> IO () -- ^ setColour a1 a2 = withHG3DClass a1 $ \a1' -> withColour a2 $ \a2' -> setColour'_ a1' a2' >>= \res -> return () {-# LINE 98 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Gets the colour of this billboard. getColour :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Colour) -- ^ getColour a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getColour'_ a1' a2' >>= \res -> peekColour a2'>>= \a2'' -> return (a2'') {-# LINE 103 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Returns true if this billboard deviates from the BillboardSetBillboard::setDimensionsBillboard::setDimensions hasOwnDimensions :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ hasOwnDimensions a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> hasOwnDimensions'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 108 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Retrieves the billboard's personal width, if hasOwnDimensions is true. getOwnWidth :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Float) -- ^ getOwnWidth a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getOwnWidth'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 113 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Retrieves the billboard's personal width, if hasOwnDimensions is true. getOwnHeight :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Float) -- ^ getOwnHeight a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getOwnHeight'_ a1' a2' >>= \res -> peekFloatConv a2'>>= \a2'' -> return (a2'') {-# LINE 118 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | Returns true if this billboard use individual texture coordinate rect (i.e. if the Billboard::setTexcoordRectBillboardSetBillboard::setTexcoordIndexBillboard::setTexcoordIndex()Billboard::setTexcoordRect() isUseTexcoordRect :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Bool) -- ^ isUseTexcoordRect a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> isUseTexcoordRect'_ a1' a2' >>= \res -> peekBoolUtil a2'>>= \a2'' -> return (a2'') {-# LINE 123 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | setTexcoordIndex()BillboardSet::setTextureCoords() setTexcoordIndex :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Int -- ^ texcoordIndex -> IO () -- ^ setTexcoordIndex a1 a2 = withHG3DClass a1 $ \a1' -> let {a2' = fromIntegral a2} in setTexcoordIndex'_ a1' a2' >>= \res -> return () {-# LINE 128 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | getTexcoordIndex()setTexcoordIndex()This value is useful only when isUseTexcoordRect return false. getTexcoordIndex :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> IO (Int) -- ^ getTexcoordIndex a1 = withHG3DClass a1 $ \a1' -> alloca $ \a2' -> getTexcoordIndex'_ a1' a2' >>= \res -> peekIntConv a2'>>= \a2'' -> return (a2'') {-# LINE 133 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} -- | setTexcoordRect() setTexcoordRect2 :: HG3DClass -- ^ classpointer - pointer of Class instance from which this methods is called. -> Float -- ^ u0 -> Float -- ^ v0 -> Float -- ^ u1 -> Float -- ^ v1 -> IO () -- ^ setTexcoordRect2 a1 a2 a3 a4 a5 = withHG3DClass a1 $ \a1' -> let {a2' = realToFrac a2} in let {a3' = realToFrac a3} in let {a4' = realToFrac a4} in let {a5' = realToFrac a5} in setTexcoordRect2'_ a1' a2' a3' a4' a5' >>= \res -> return () {-# LINE 141 ".\\HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs" #-} foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_construct" new'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_destruct" delete'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_getRotation" getRotation'_ :: ((HG3DClassPtr) -> ((RadiansPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_setRotation" setRotation'_ :: ((HG3DClassPtr) -> ((RadiansPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_setPosition" setPosition'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_setPosition2" setPosition2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (IO ()))))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_getPosition" getPosition'_ :: ((HG3DClassPtr) -> ((Vec3Ptr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_setDimensions" setDimensions'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (IO ())))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_resetDimensions" resetDimensions'_ :: ((HG3DClassPtr) -> (IO ())) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_setColour" setColour'_ :: ((HG3DClassPtr) -> ((ColourPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_getColour" getColour'_ :: ((HG3DClassPtr) -> ((ColourPtr) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_hasOwnDimensions" hasOwnDimensions'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_getOwnWidth" getOwnWidth'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_getOwnHeight" getOwnHeight'_ :: ((HG3DClassPtr) -> ((Ptr CFloat) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_isUseTexcoordRect" isUseTexcoordRect'_ :: ((HG3DClassPtr) -> ((Ptr CInt) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_setTexcoordIndex" setTexcoordIndex'_ :: ((HG3DClassPtr) -> (CUShort -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_getTexcoordIndex" getTexcoordIndex'_ :: ((HG3DClassPtr) -> ((Ptr CUShort) -> (IO ()))) foreign import ccall safe "HGamer3D\\Bindings\\Ogre\\ClassBillboard.chs.h ogre_bbd_setTexcoordRect2" setTexcoordRect2'_ :: ((HG3DClassPtr) -> (CFloat -> (CFloat -> (CFloat -> (CFloat -> (IO ()))))))