module Graphics.LambdaCube.HardwareVertexBuffer where import Data.Word import Data.IntMap import Foreign.Marshal.Alloc import Foreign.Marshal.Utils import Foreign.Storable import Foreign.C.Types import Foreign.Ptr import Data.IORef import Control.Monad import Graphics.LambdaCube.HardwareBuffer class (HardwareBuffer a) => HardwareVertexBuffer a where getVertexSize :: a -> Int -- ^ Gets the size in bytes of a single vertex in this buffer getNumVertices :: a -> Int -- ^ Get the number of vertices in this buffer -- | Vertex element semantics, used to identify the meaning of vertex buffer contents data VertexElementSemantic = VES_POSITION -- ^ Position, 3 reals per vertex | VES_BLEND_WEIGHTS -- ^ Blending weights | VES_BLEND_INDICES -- ^ Blending indices | VES_NORMAL -- ^ Normal, 3 reals per vertex | VES_DIFFUSE -- ^ Diffuse colours | VES_SPECULAR -- ^ Specular colours | VES_TEXTURE_COORDINATES -- ^ Texture coordinates | VES_BINORMAL -- ^ Binormal (Y axis if normal is Z) | VES_TANGENT -- ^ Tangent (X axis if normal is Z) deriving (Enum,Eq,Ord,Show) -- | Vertex element type, used to identify the base types of the vertex contents data VertexElementType = VET_FLOAT1 | VET_FLOAT2 | VET_FLOAT3 | VET_FLOAT4 -- -- | alias to more specific colour type - use the current rendersystem's colour packing -- | VET_COLOUR -- Deprecated by Ogre | VET_SHORT1 | VET_SHORT2 | VET_SHORT3 | VET_SHORT4 | VET_UBYTE4 -- | D3D style compact colour | VET_COLOUR_ARGB -- | GL style compact colour | VET_COLOUR_ABGR deriving (Eq,Ord,Show) {-| This class declares the usage of a single vertex buffer as a component of a complete VertexDeclaration. @remarks Several vertex buffers can be used to supply the input geometry for a rendering operation, and in each case a vertex buffer can be used in different ways for different operations; the buffer itself does not define the semantics (position, normal etc), the VertexElement class does. -} data VertexElement = VertexElement { veSource :: Int -- ^ The source vertex buffer, as bound to an index using VertexBufferBinding , veOffset :: Int -- ^ The offset in the buffer that this element starts at , veType :: VertexElementType -- ^ The type of element , veSemantic :: VertexElementSemantic -- ^ The meaning of the element , veIndex :: Int -- ^ Index of the item, only applicable for some elements like texture coords } deriving (Eq,Ord,Show) -- | Utility method for helping to calculate offsets getTypeSize :: VertexElementType -> Int getTypeSize etype = case etype of { VET_COLOUR_ABGR -> sizeOf (undefined::Word32) -- sizeof(RGBA); ; VET_COLOUR_ARGB -> sizeOf (undefined::Word32) -- sizeof(RGBA); ; VET_FLOAT1 -> sizeOf (undefined::CFloat) -- sizeof(float); ; VET_FLOAT2 -> 2 * sizeOf (undefined::CFloat) -- sizeof(float)*2; ; VET_FLOAT3 -> 3 * sizeOf (undefined::CFloat) -- sizeof(float)*3; ; VET_FLOAT4 -> 4 * sizeOf (undefined::CFloat) -- sizeof(float)*4; ; VET_SHORT1 -> sizeOf (undefined::CShort) -- sizeof(short); ; VET_SHORT2 -> 2 * sizeOf (undefined::CShort) -- sizeof(short)*2; ; VET_SHORT3 -> 3 * sizeOf (undefined::CShort) -- sizeof(short)*3; ; VET_SHORT4 -> 4 * sizeOf (undefined::CShort) -- sizeof(short)*4; ; VET_UBYTE4 -> 4 * sizeOf (undefined::CUChar) -- sizeof(unsigned char)*4; } -- | Utility method which returns the count of values in a given type getTypeCount :: VertexElementType -> Int getTypeCount etype = case etype of { VET_COLOUR_ABGR -> 1 ; VET_COLOUR_ARGB -> 1 ; VET_FLOAT1 -> 1 ; VET_FLOAT2 -> 2 ; VET_FLOAT3 -> 3 ; VET_FLOAT4 -> 4 ; VET_SHORT1 -> 1 ; VET_SHORT2 -> 2 ; VET_SHORT3 -> 3 ; VET_SHORT4 -> 4 ; VET_UBYTE4 -> 4 } {-| Simple converter function which will turn a single-value type into a multi-value type based on a parameter. -} multiplyTypeCount :: VertexElementType -> Int -> VertexElementType multiplyTypeCount baseType count = case baseType of { VET_FLOAT1 -> case count of { 1 -> VET_FLOAT1 ; 2 -> VET_FLOAT2 ; 3 -> VET_FLOAT3 ; 4 -> VET_FLOAT4 ; _ -> error "Invalid type" } ; VET_SHORT1 -> case count of { 1 -> VET_SHORT1 ; 2 -> VET_SHORT2 ; 3 -> VET_SHORT3 ; 4 -> VET_SHORT4 ; _ -> error "Invalid type" } ; _ -> error "Invalid type" } {-| Simple converter function which will a type into it's single-value equivalent - makes switches on type easier. -} getBaseType :: VertexElementType -> VertexElementType getBaseType multiType = case multiType of { VET_FLOAT1 -> VET_FLOAT1 ; VET_FLOAT2 -> VET_FLOAT2 ; VET_FLOAT3 -> VET_FLOAT3 ; VET_FLOAT4 -> VET_FLOAT4 ; VET_COLOUR_ABGR -> VET_COLOUR_ABGR ; VET_COLOUR_ARGB -> VET_COLOUR_ARGB ; VET_SHORT1 -> VET_SHORT1 ; VET_SHORT2 -> VET_SHORT2 ; VET_SHORT3 -> VET_SHORT3 ; VET_SHORT4 -> VET_SHORT4 ; VET_UBYTE4 -> VET_UBYTE4 } {-| Utility method for converting colour from one packed 32-bit colour type to another. @param srcType The source type @param dstType The destination type @param ptr Read / write value to change -} --static void convertColourValue(VertexElementType srcType, -- VertexElementType dstType, uint32* ptr); {-| Utility method for converting colour to a packed 32-bit colour type. @param src source colour @param dst The destination type -} --static uint32 convertColourValue(const ColourValue& src, -- VertexElementType dst); {-| Utility method to get the most appropriate packed colour vertex element format. -} --static VertexElementType getBestColourVertexElementType(void); data VertexDeclaration = VertexDeclaration { vdElementList :: [VertexElement] -- ^ Defines the list of vertex elements that makes up this declaration } deriving (Eq,Show) {-| Records the state of all the vertex buffer bindings required to provide a vertex declaration with the input data it needs for the vertex elements. @remarks Why do we have this binding list rather than just have VertexElement referring to the vertex buffers direct? Well, in the underlying APIs, binding the vertex buffers to an index (or 'stream') is the way that vertex data is linked, so this structure better reflects the realities of that. In addition, by separating the vertex declaration from the list of vertex buffer bindings, it becomes possible to reuse bindings between declarations and vice versa, giving opportunities to reduce the state changes required to perform rendering. @par Like the other classes in this functional area, these binding maps should be created and destroyed using the HardwareBufferManager. -} data HardwareVertexBuffer vb => VertexBufferBinding vb = VertexBufferBinding { vbbBindingMap :: IntMap vb } deriving Eq