module Graphics.LambdaCube.Mesh where import Data.Maybe import Foreign import Foreign.C.Types import qualified Data.IntMap as IntMap import Unsafe.Coerce -- because realToFrac just doesn't cut it... import Graphics.LambdaCube.HardwareBuffer import Graphics.LambdaCube.HardwareIndexBuffer import Graphics.LambdaCube.HardwareVertexBuffer import Graphics.LambdaCube.RenderOperation import Graphics.LambdaCube.Types import Graphics.LambdaCube.Utility import Graphics.LambdaCube.VertexIndexData data (HardwareVertexBuffer vb, HardwareIndexBuffer ib) => SubMesh vb ib = SubMesh { smOperationType :: OperationType -- ^ The render operation type used to render this submesh , 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 -- , smExtremityPoints :: [FloatType3] , smMaterialName :: String -- ^ Name of the material this SubMesh uses. } data (HardwareVertexBuffer vb, HardwareIndexBuffer ib) => Mesh vb ib = Mesh { msSubMeshList :: [SubMesh vb ib] -- , msSubMeshNameMap :: Map String Int , msBoundRadius :: FloatType -- , msSkeletonName :: String -- , msVertexBufferUsage :: Usage -- , msIndexBufferUsage :: Usage -- , msVertexBufferShadowBuffer :: Bool -- , msIndexBufferShadowBuffer :: Bool , msSharedVertexData :: Maybe (VertexData vb) } -- TODO calculateBoundingRadius :: (HardwareVertexBuffer vb, HardwareIndexBuffer ib) => Mesh vb ib -> IO FloatType calculateBoundingRadius mesh = do let processSubMesh r sm = do -- get pointer to position vertex attribute container array let Just vd = if isNothing (smVertexData sm) then msSharedVertexData mesh else smVertexData sm posve = head $ filter ((VES_POSITION ==) . veSemantic) $ vdElementList $ vdVertexDeclaration vd vb = (vbbBindingMap $ vdVertexBufferBinding vd) IntMap.! (veSource posve) -- lock vb and ib for reading offs = veOffset posve stride = getVertexSize vb pb <- lock vb offs (getSizeInBytes vb - offs) HBL_READ_ONLY let getVertexDistance l i = do let p :: Ptr CFloat p = plusPtr pb $ i * stride f = unsafeCoerce :: CFloat -> Float [x,y,z] <- peekArray 3 p return $ max l $ f $ sqrt $ x*x + y*y + z*z -- pass through buffer and process triangles d <- foldM' getVertexDistance r [0..getNumVertices vb-1] unlock vb return d foldM' processSubMesh 0 $ msSubMeshList mesh