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:
parent
138d16016b
commit
1bc65c8ea7
@ -28,10 +28,11 @@ import Control.Monad
|
|||||||
import Foreign.Ptr
|
import Foreign.Ptr
|
||||||
import Foreign.Marshal.Alloc
|
import Foreign.Marshal.Alloc
|
||||||
import Foreign.Marshal.Utils
|
import Foreign.Marshal.Utils
|
||||||
|
import Foreign.Storable (sizeOf)
|
||||||
|
|
||||||
import Prelude as P hiding (take, null)
|
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]
|
-- | helper-function for creating an integral out of [8-Bit Ints]
|
||||||
_w8ToInt :: Integral a => a -> a -> a
|
_w8ToInt :: Integral a => a -> a -> a
|
||||||
@ -221,12 +222,16 @@ parseIQM a =
|
|||||||
let va = vertexArrays raw
|
let va = vertexArrays raw
|
||||||
va' <- mapM (readInVAO f (num_vertexes.header $ raw)) va
|
va' <- mapM (readInVAO f (num_vertexes.header $ raw)) va
|
||||||
vbo <- mapM toVBOfromVAO va
|
vbo <- mapM toVBOfromVAO va
|
||||||
|
tris <- copyTriangles raw f
|
||||||
withVAO vao $ createVAO (zip va' vbo)
|
withVAO vao $ createVAO (zip va' vbo)
|
||||||
|
putStrLn "Triangles:"
|
||||||
|
printPtrAsWord32Array tris ((*3).fromIntegral.num_triangles.header $ raw) 3
|
||||||
print raw
|
print raw
|
||||||
return $ raw
|
return $ raw
|
||||||
{ vertexArrays = va'
|
{ vertexArrays = va'
|
||||||
, vertexBufferObjects = vbo
|
, vertexBufferObjects = vbo
|
||||||
, vertexArrayObject = vao
|
, vertexArrayObject = vao
|
||||||
|
, triangles = tris
|
||||||
}
|
}
|
||||||
|
|
||||||
createVAO :: [(IQMVertexArray, BufferObject)] -> IO ()
|
createVAO :: [(IQMVertexArray, BufferObject)] -> IO ()
|
||||||
@ -246,6 +251,17 @@ initVAO l t bo = do
|
|||||||
vertexAttribArray l $= Enabled
|
vertexAttribArray l $= Enabled
|
||||||
vertexAttribPointer l $= (ToFloat, VertexArrayDescriptor num Float 0 nullPtr)
|
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
|
-- | 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: "]
|
putStrLn $ concat ["Filling starting at ", show offset, " with: "]
|
||||||
unsafeUseAsCString data' (\s -> copyBytes p s byteLen)
|
unsafeUseAsCString data' (\s -> copyBytes p s byteLen)
|
||||||
case type' of
|
case type' of
|
||||||
IQMBlendIndexes -> printPtrAsUByteArray p numElems
|
IQMBlendIndexes -> printPtrAsUByteArray p numElems 4
|
||||||
IQMBlendWeights -> printPtrAsUByteArray p numElems
|
IQMBlendWeights -> printPtrAsUByteArray p numElems 4
|
||||||
_ -> printPtrAsFloatArray p numElems
|
IQMTexCoord -> printPtrAsFloatArray p numElems 2
|
||||||
|
_ -> printPtrAsFloatArray p numElems 3
|
||||||
return $ IQMVertexArray type' a format num offset $ castPtr p
|
return $ IQMVertexArray type' a format num offset $ castPtr p
|
||||||
|
|
||||||
-- | Real internal Parser.
|
-- | Real internal Parser.
|
||||||
@ -311,6 +328,7 @@ doIQMparse vao =
|
|||||||
, vertexArrays = vaf
|
, vertexArrays = vaf
|
||||||
, vertexBufferObjects = [] --initialized later, after vaf get allocated.
|
, vertexBufferObjects = [] --initialized later, after vaf get allocated.
|
||||||
, vertexArrayObject = vao
|
, vertexArrayObject = vao
|
||||||
|
, triangles = nullPtr --initialized later, after memory gets allocated.
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Helper-Function for Extracting a random substring out of a Bytestring
|
-- | Helper-Function for Extracting a random substring out of a Bytestring
|
||||||
|
@ -112,6 +112,7 @@ data IQM = IQM
|
|||||||
, vertexArrays :: [IQMVertexArray]
|
, vertexArrays :: [IQMVertexArray]
|
||||||
, vertexBufferObjects :: [BufferObject]
|
, vertexBufferObjects :: [BufferObject]
|
||||||
, vertexArrayObject :: VertexArrayObject
|
, vertexArrayObject :: VertexArrayObject
|
||||||
|
, triangles :: Ptr Word32
|
||||||
} deriving (Show, Eq)
|
} deriving (Show, Eq)
|
||||||
|
|
||||||
-- | Different Vertex-Array-Types in IQM
|
-- | Different Vertex-Array-Types in IQM
|
||||||
@ -202,6 +203,6 @@ instance Show IQMVertexArray where
|
|||||||
", Format: " ++ show fo ++
|
", Format: " ++ show fo ++
|
||||||
", NumComponents: " ++ show nc ++
|
", NumComponents: " ++ show nc ++
|
||||||
", Offset: " ++ show off ++
|
", Offset: " ++ show off ++
|
||||||
", Data at: " ++ show dat ++
|
", Data at: " ++ show dat ++
|
||||||
")"
|
")"
|
||||||
|
|
||||||
|
@ -3,6 +3,7 @@ module Render.Misc where
|
|||||||
import Control.Monad
|
import Control.Monad
|
||||||
import qualified Data.ByteString as B (ByteString)
|
import qualified Data.ByteString as B (ByteString)
|
||||||
import Data.Int (Int8)
|
import Data.Int (Int8)
|
||||||
|
import Data.Word (Word32)
|
||||||
import Graphics.Rendering.OpenGL.GL.Shaders
|
import Graphics.Rendering.OpenGL.GL.Shaders
|
||||||
import Graphics.Rendering.OpenGL.GL.StateVar
|
import Graphics.Rendering.OpenGL.GL.StateVar
|
||||||
import Graphics.Rendering.OpenGL.GL.StringQueries
|
import Graphics.Rendering.OpenGL.GL.StringQueries
|
||||||
@ -78,7 +79,7 @@ createFrustum fov n' f' rat =
|
|||||||
|
|
||||||
-- | Creates an orthogonal frustum with given width, height, near and far-plane
|
-- | Creates an orthogonal frustum with given width, height, near and far-plane
|
||||||
createFrustumOrtho :: Float -> Float -> Float -> Float -> M44 CFloat
|
createFrustumOrtho :: Float -> Float -> Float -> Float -> M44 CFloat
|
||||||
createFrustumOrtho w' h' n' f' =
|
createFrustumOrtho w' h' n' f' =
|
||||||
let [w,h,n,f] = map realToFrac [w',h',n',f']
|
let [w,h,n,f] = map realToFrac [w',h',n',f']
|
||||||
in
|
in
|
||||||
V4 (V4 (0.5/w) 0 0 0)
|
V4 (V4 (0.5/w) 0 0 0)
|
||||||
@ -123,17 +124,23 @@ getCam (x',z') dist' xa' ya' = lookAt (cpos ^+^ at') at' up
|
|||||||
xa = realToFrac xa'
|
xa = realToFrac xa'
|
||||||
ya = realToFrac ya'-}
|
ya = realToFrac ya'-}
|
||||||
|
|
||||||
-- | Prints any Pointer as Float-Array with given number of elements.
|
-- | Prints any Pointer as Float-Array with given number of elements and chunks.
|
||||||
printPtrAsFloatArray :: Ptr a -> Int -> IO ()
|
printPtrAsFloatArray :: Ptr a -> Int -> Int -> IO ()
|
||||||
printPtrAsFloatArray pointer num = do
|
printPtrAsFloatArray pointer num co = do
|
||||||
a <- peekArray num (castPtr pointer :: Ptr CFloat)
|
a <- peekArray num (castPtr pointer :: Ptr CFloat)
|
||||||
print a
|
print $ chunksOf co a
|
||||||
|
|
||||||
-- | Prints any Pointer as UByte-Array with given number of elements.
|
-- | Prints any Pointer as UByte-Array with given number of elements and chunks.
|
||||||
printPtrAsUByteArray :: Ptr a -> Int -> IO ()
|
printPtrAsUByteArray :: Ptr a -> Int -> Int -> IO ()
|
||||||
printPtrAsUByteArray pointer num = do
|
printPtrAsUByteArray pointer num co = do
|
||||||
a <- peekArray num (castPtr pointer :: Ptr CUChar)
|
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 :: Ord a => a -> a -> a -> a
|
||||||
curb l h x
|
curb l h x
|
||||||
@ -152,3 +159,7 @@ genColorData :: Int -- ^ Amount
|
|||||||
-> [Int8] -- ^ [r,g,b,a], [r,g,b] - whatever should be repeatet.
|
-> [Int8] -- ^ [r,g,b,a], [r,g,b] - whatever should be repeatet.
|
||||||
-> [Int8]
|
-> [Int8]
|
||||||
genColorData n c = take (length c*n) (cycle c)
|
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 :: IQM -> L.V3 CFloat -> L.V3 CFloat -> IO ()
|
||||||
renderIQM m p@(L.V3 x y z) s@(L.V3 sx sy sz) = do
|
renderIQM m p@(L.V3 x y z) s@(L.V3 sx sy sz) = do
|
||||||
bindVertexArrayObject $= Just (vertexArrayObject m)
|
bindVertexArrayObject $= Just (vertexArrayObject m)
|
||||||
let n = num_vertexes.header $ m
|
let n = fromIntegral.num_triangles.header $ m
|
||||||
--print $ concat ["drawing ", show n," triangles from object ",show m]
|
--print $ concat ["drawing ", show n," triangles"]
|
||||||
drawArrays Triangles 0 (fromIntegral n)
|
drawElements Triangles n UnsignedInt (triangles m)
|
||||||
checkError "drawing model"
|
checkError "drawing model"
|
||||||
return ()
|
return ()
|
||||||
|
|
||||||
@ -325,7 +325,7 @@ drawMap = do
|
|||||||
glPatchParameteri gl_PATCH_VERTICES 3
|
glPatchParameteri gl_PATCH_VERTICES 3
|
||||||
|
|
||||||
cullFace $= Nothing --Just Front
|
cullFace $= Nothing --Just Front
|
||||||
polygonMode $= (Line,Line)
|
polygonMode $= (Fill,Fill)
|
||||||
|
|
||||||
glDrawArrays gl_PATCHES 0 (fromIntegral numVert)
|
glDrawArrays gl_PATCHES 0 (fromIntegral numVert)
|
||||||
|
|
||||||
|
Loading…
Reference in New Issue
Block a user