module Graphics.LambdaCube.Mesh where import Data.Map (Map) import qualified Data.Map as Map import Graphics.LambdaCube.Types import Graphics.LambdaCube.RenderOperation import Graphics.LambdaCube.HardwareBuffer import Graphics.LambdaCube.HardwareVertexBuffer import Graphics.LambdaCube.HardwareIndexBuffer import Graphics.LambdaCube.VertexIndexData data (HardwareVertexBuffer vb, HardwareIndexBuffer ib) => SubMesh vb ib = SubMesh { smOperationType :: OperationType -- ^ The render operation type used to render this submesh {-| Dedicated vertex data (only valid if useSharedVertices = false). @remarks This data is completely owned by this submesh. @par The use of shared or non-shared buffers is determined when model data is converted to the OGRE .mesh format. -} , smVertexData :: Maybe (VertexData vb) -- ^ Indicates if this submesh shares vertex data with other meshes or whether it has it's own vertices. , smIndexData :: Maybe (IndexData ib) -- ^ Face index data {-| Dedicated index map for translate blend index to bone index (only valid if useSharedVertices = false). @remarks This data is completely owned by this submesh. @par We collect actually used bones of all bone assignments, and build the blend index in 'packed' form, then the range of the blend index in vertex data VES_BLEND_INDICES element is continuous, with no gaps. Thus, by minimising the world matrix array constants passing to GPU, we can support more bones for a mesh when hardware skinning is used. The hardware skinning support limit is applied to each set of vertex data in the mesh, in other words, the hardware skinning support limit is applied only to the actually used bones of each SubMeshes, not all bones across the entire Mesh. @par Because the blend index is different to the bone index, therefore, we use the index map to translate the blend index to bone index. @par The use of shared or non-shared index map is determined when model data is converted to the OGRE .mesh format. -} --typedef vector::type IndexMap; --IndexMap blendIndexToBoneIndexMap; --ProgressiveMesh::LODFaceList mLodFaceList; {-| A list of extreme points on the submesh (optional). @remarks These points are some arbitrary points on the mesh that are used by engine to better sort submeshes by depth. This doesn't matter much for non-transparent submeshes, as Z-buffer takes care of invisible surface culling anyway, but is pretty useful for semi-transparent submeshes because the order in which transparent submeshes must be rendered cannot be always correctly deduced from entity position. @par These points are intelligently chosen from the points that make up the submesh, the criteria for choosing them should be that these points somewhat characterize the submesh outline, e.g. they should not be close to each other, and they should be on the outer hull of the submesh. They can be stored in the .mesh file, or generated at runtime (see generateExtremes ()). @par If this array is empty, submesh sorting is done like in older versions - by comparing the positions of the owning entity. -} , smExtremityPoints :: [FloatType3] , smMaterialName :: String -- ^ Name of the material this SubMesh uses. -- | Is there a material yet? -- bool mMatInitialised; -- | paired list of texture aliases and texture names -- AliasTextureNamePairList mTextureAliases; -- VertexBoneAssignmentList mBoneAssignments; -- | Flag indicating that bone assignments need to be recompiled -- bool mBoneAssignmentsOutOfDate; -- | Type of vertex animation for dedicated vertex data (populated by Mesh) -- mutable VertexAnimationType mVertexAnimationType; -- | Is Build Edges Enabled -- bool mBuildEdgesEnabled; } data (HardwareVertexBuffer vb, HardwareIndexBuffer ib) => Mesh vb ib = Mesh { msSubMeshList :: [SubMesh vb ib] {-| A hashmap used to store optional SubMesh names. Translates a name into SubMesh index -} --typedef HashMap SubMeshNameMap ; --ected: --DataStreamPtr mFreshFromDisk; --SubMeshNameMap mSubMeshNameMap ; , msSubMeshNameMap :: Map String Int -- | Local bounding box volume -- TODO: AxisAlignedBox mAABB; ---- | Local bounding sphere radius (centered on object) , msBoundRadius :: FloatType -- | Optional linked skeleton , msSkeletonName :: String -- TODO: , msSkeleton :: Skeleton -- TODO: VertexBoneAssignmentList mBoneAssignments; -- | Flag indicating that bone assignments need to be recompiled -- TODO: bool mBoneAssignmentsOutOfDate; -- TODO: const LodStrategy *mLodStrategy; -- TODO: bool mIsLodManual; -- TODO: ushort mNumLods; -- TODO: MeshLodUsageList mMeshLodUsageList; , msVertexBufferUsage :: Usage , msIndexBufferUsage :: Usage , msVertexBufferShadowBuffer :: Bool , msIndexBufferShadowBuffer :: Bool -- TODO: bool mPreparedForShadowVolumes; -- TODO: bool mEdgeListsBuilt; -- TODO: bool mAutoBuildEdgeLists; -- | Storage of morph animations, lookup by name -- TODO: typedef map::type AnimationList; -- TODO: AnimationList mAnimationsList; -- | The vertex animation type associated with the shared vertex data -- TODO: mutable VertexAnimationType mSharedVertexDataAnimationType; -- | Do we need to scan animations for animation types? -- TODO: mutable bool mAnimationTypesDirty; -- | List of available poses for shared and dedicated geometryPoseList -- TODO: PoseList mPoseList; {-| Shared vertex data. @remarks This vertex data can be shared among multiple submeshes. SubMeshes may not have their own VertexData, they may share this one. @par The use of shared or non-shared buffers is determined when model data is converted to the OGRE .mesh format. -} , msSharedVertexData :: Maybe (VertexData vb) {-| Shared index map for translating blend index to bone index. @remarks This index map can be shared among multiple submeshes. SubMeshes might not have their own IndexMap, they might share this one. @par We collect actually used bones of all bone assignments, and build the blend index in 'packed' form, then the range of the blend index in vertex data VES_BLEND_INDICES element is continuous, with no gaps. Thus, by minimising the world matrix array constants passing to GPU, we can support more bones for a mesh when hardware skinning is used. The hardware skinning support limit is applied to each set of vertex data in the mesh, in other words, the hardware skinning support limit is applied only to the actually used bones of each SubMeshes, not all bones across the entire Mesh. @par Because the blend index is different to the bone index, therefore, we use the index map to translate the blend index to bone index. @par The use of shared or non-shared index map is determined when model data is converted to the OGRE .mesh format. -} -- TODO: IndexMap sharedBlendIndexToBoneIndexMap; } {- -- TODO: create generic functions which operate on buffer elements mapFloatType3M_ :: (FloatType -> FloatType -> FloatType -> IO a) -> (Int,Ptr FloatType,Int) -> IO () mapFloatType3M_ f (cnt,ptr,stride) = do let s' = if stride == 0 then 4 else stride mapM_ (g ptr s') [0..(cnt-1)] where g ptr stride i = do let p = plusPtr ptr $ stride * i x <- peekElemOff p 0 y <- peekElemOff p 1 z <- peekElemOff p 2 f x y z foldFloatType3M :: ((FloatType,FloatType,FloatType) -> b -> b) -> b -> (Int,Ptr FloatType,Int) -> IO b foldFloatType3M f a (cnt,ptr,stride) = do let s' = if stride == 0 then 4 else stride foldM (g ptr s') a [0..(cnt-1)] where g ptr stride e i = do let p = plusPtr ptr $ stride * i x <- peekElemOff p 0 y <- peekElemOff p 1 z <- peekElemOff p 2 return $ f (x,y,z) e -} --calculateBoundingRadius :: Mesh -> IO FloatType --calculateBoundingRadius m = do -- collect vertex data -- find -- return