added triangles to IQM-Parsing
- Models should now use the right "drawElements"-Method - still no sign of our box-model
This commit is contained in:
		| @@ -28,10 +28,11 @@ import Control.Monad | ||||
| import Foreign.Ptr | ||||
| import Foreign.Marshal.Alloc | ||||
| import Foreign.Marshal.Utils | ||||
| import Foreign.Storable (sizeOf) | ||||
|  | ||||
| import Prelude as P hiding (take, null) | ||||
|  | ||||
| import Render.Misc (printPtrAsFloatArray, printPtrAsUByteArray) | ||||
| import Render.Misc (printPtrAsFloatArray, printPtrAsUByteArray, printPtrAsWord32Array) | ||||
|  | ||||
| -- | helper-function for creating an integral out of [8-Bit Ints] | ||||
| _w8ToInt :: Integral a => a -> a -> a | ||||
| @@ -221,12 +222,16 @@ parseIQM a = | ||||
|     let va = vertexArrays raw | ||||
|     va' <- mapM (readInVAO f (num_vertexes.header $ raw)) va | ||||
|     vbo <- mapM toVBOfromVAO va | ||||
|     tris <- copyTriangles raw f | ||||
|     withVAO vao $ createVAO (zip va' vbo) | ||||
|     putStrLn "Triangles:" | ||||
|     printPtrAsWord32Array tris ((*3).fromIntegral.num_triangles.header $ raw) 3 | ||||
|     print raw | ||||
|     return $ raw | ||||
|         { vertexArrays = va' | ||||
|         , vertexBufferObjects = vbo | ||||
|         , vertexArrayObject = vao | ||||
|         , triangles = tris | ||||
|         } | ||||
|  | ||||
| createVAO :: [(IQMVertexArray, BufferObject)] -> IO () | ||||
| @@ -246,6 +251,17 @@ initVAO l t bo = do | ||||
| 	vertexAttribArray l $= Enabled | ||||
| 	vertexAttribPointer l $= (ToFloat, VertexArrayDescriptor num Float 0 nullPtr) | ||||
|  | ||||
| copyTriangles :: IQM -> ByteString -> IO (Ptr Word32) | ||||
| copyTriangles i f = | ||||
|     do | ||||
|         let | ||||
|             len = fromIntegral $ num_triangles $ header i | ||||
|             byteLen = len * 3 * sizeOf (undefined :: Word32) | ||||
|             data' = skipDrop (fromIntegral $ ofs_triangles $ header i) byteLen f | ||||
|         p <- mallocBytes byteLen | ||||
|         unsafeUseAsCString data' (\s -> copyBytes p s byteLen) | ||||
|         return $ castPtr p | ||||
|  | ||||
|  | ||||
| -- | Creates a BufferObject on the Graphicscard for each BufferObject | ||||
|  | ||||
| @@ -283,9 +299,10 @@ readInVAO d vcount (IQMVertexArray type' a format num offset ptr) = | ||||
|         putStrLn $ concat ["Filling starting at ", show offset, " with: "] | ||||
|         unsafeUseAsCString data' (\s -> copyBytes p s byteLen) | ||||
|         case type' of | ||||
|             IQMBlendIndexes -> printPtrAsUByteArray p numElems | ||||
|             IQMBlendWeights -> printPtrAsUByteArray p numElems | ||||
|             _ -> printPtrAsFloatArray p numElems | ||||
|             IQMBlendIndexes -> printPtrAsUByteArray p numElems 4 | ||||
|             IQMBlendWeights -> printPtrAsUByteArray p numElems 4 | ||||
|             IQMTexCoord     -> printPtrAsFloatArray p numElems 2 | ||||
|             _ -> printPtrAsFloatArray p numElems 3 | ||||
|         return $ IQMVertexArray type' a format num offset $ castPtr p | ||||
|  | ||||
| -- | Real internal Parser. | ||||
| @@ -311,6 +328,7 @@ doIQMparse vao = | ||||
|                     , vertexArrays = vaf | ||||
|                     , vertexBufferObjects = [] --initialized later, after vaf get allocated. | ||||
|                     , vertexArrayObject = vao | ||||
|                     , triangles = nullPtr      --initialized later, after memory gets allocated. | ||||
|                     } | ||||
|  | ||||
| -- | Helper-Function for Extracting a random substring out of a Bytestring | ||||
|   | ||||
| @@ -112,6 +112,7 @@ data IQM = IQM | ||||
|         , vertexArrays          :: [IQMVertexArray] | ||||
|         , vertexBufferObjects   :: [BufferObject] | ||||
|         , vertexArrayObject     :: VertexArrayObject | ||||
|         , triangles             :: Ptr Word32 | ||||
|         } deriving (Show, Eq) | ||||
|  | ||||
| -- | Different Vertex-Array-Types in IQM | ||||
|   | ||||
| @@ -3,6 +3,7 @@ module Render.Misc where | ||||
| import           Control.Monad | ||||
| import qualified Data.ByteString                            as B (ByteString) | ||||
| import           Data.Int                                   (Int8) | ||||
| import           Data.Word                                  (Word32) | ||||
| import           Graphics.Rendering.OpenGL.GL.Shaders | ||||
| import           Graphics.Rendering.OpenGL.GL.StateVar | ||||
| import           Graphics.Rendering.OpenGL.GL.StringQueries | ||||
| @@ -123,17 +124,23 @@ getCam (x',z') dist' xa' ya' = lookAt (cpos ^+^ at') at' up | ||||
|                         xa    = realToFrac xa' | ||||
|                         ya    = realToFrac ya'-} | ||||
|  | ||||
| -- | Prints any Pointer as Float-Array with given number of elements.  | ||||
| printPtrAsFloatArray :: Ptr a -> Int -> IO () | ||||
| printPtrAsFloatArray pointer num = do | ||||
| -- | Prints any Pointer as Float-Array with given number of elements and chunks. | ||||
| printPtrAsFloatArray :: Ptr a -> Int -> Int -> IO () | ||||
| printPtrAsFloatArray pointer num co = do | ||||
|                         a <- peekArray num (castPtr pointer :: Ptr CFloat) | ||||
|                         print a | ||||
|                         print $ chunksOf co a | ||||
|  | ||||
| -- | Prints any Pointer as UByte-Array with given number of elements.  | ||||
| printPtrAsUByteArray :: Ptr a -> Int -> IO () | ||||
| printPtrAsUByteArray pointer num = do | ||||
| -- | Prints any Pointer as UByte-Array with given number of elements and chunks. | ||||
| printPtrAsUByteArray :: Ptr a -> Int -> Int -> IO () | ||||
| printPtrAsUByteArray pointer num co = do | ||||
|                         a <- peekArray num (castPtr pointer :: Ptr CUChar) | ||||
|                         print a | ||||
|                         print $ chunksOf co a | ||||
|  | ||||
| -- | Prints any Pointer as Word32-Array with given number of elements and chunks. | ||||
| printPtrAsWord32Array :: Ptr a -> Int -> Int -> IO () | ||||
| printPtrAsWord32Array pointer num co = do | ||||
|                         a <- peekArray num (castPtr pointer :: Ptr Word32) | ||||
|                         print $ chunksOf co a | ||||
|  | ||||
| curb :: Ord a => a -> a -> a -> a | ||||
| curb l h x | ||||
| @@ -152,3 +159,7 @@ genColorData ::      Int  -- ^ Amount | ||||
|                 -> [Int8] -- ^ [r,g,b,a], [r,g,b] - whatever should be repeatet. | ||||
|                 -> [Int8] | ||||
| genColorData n c = take (length c*n) (cycle c) | ||||
|  | ||||
| chunksOf :: Int -> [a] -> [[a]] | ||||
| chunksOf _ [] = [] | ||||
| chunksOf a xs = take a xs : chunksOf a (drop a xs) | ||||
|   | ||||
| @@ -286,9 +286,9 @@ initRendering = do | ||||
| renderIQM :: IQM -> L.V3 CFloat -> L.V3 CFloat -> IO () | ||||
| renderIQM m p@(L.V3 x y z) s@(L.V3 sx sy sz) = do | ||||
|     bindVertexArrayObject $= Just (vertexArrayObject m) | ||||
|     let n = num_vertexes.header $ m | ||||
|     --print $ concat ["drawing ", show n," triangles from object ",show m] | ||||
|     drawArrays Triangles 0 (fromIntegral n) | ||||
|     let n = fromIntegral.num_triangles.header $ m | ||||
|     --print $ concat ["drawing ", show n," triangles"] | ||||
|     drawElements Triangles n UnsignedInt (triangles m) | ||||
|     checkError "drawing model" | ||||
|     return () | ||||
|  | ||||
| @@ -325,7 +325,7 @@ drawMap = do | ||||
|         glPatchParameteri gl_PATCH_VERTICES 3 | ||||
|  | ||||
|         cullFace $= Nothing --Just Front | ||||
|         polygonMode $= (Line,Line) | ||||
|         polygonMode $= (Fill,Fill) | ||||
|  | ||||
|         glDrawArrays gl_PATCHES 0 (fromIntegral numVert) | ||||
|  | ||||
|   | ||||
		Reference in New Issue
	
	Block a user