changed massively in Types of IQM-Loader
- massive Type-Change internally - VertexArrays are now read headerwise - IQM needs postprocessing for allocating C-Arrays of the Vertex-Objects as they cannot be guaranteed to be collected in the first pass of reading. (Normally they are sorted linear - but the offsets WOULD allow for them to be anywhere in-between the sections)
This commit is contained in:
		@@ -30,7 +30,7 @@ parseNum = (foldl1 w8ToInt) . map fromIntegral
 | 
			
		||||
-- | read a 16-Bit Int from Parsing-Input and log 2 bytes in our Parsing-Monad
 | 
			
		||||
--
 | 
			
		||||
--   begins with _ to defeat ghc-warnings. Rename if used!
 | 
			
		||||
_int16 :: CParser Int16
 | 
			
		||||
_int16 :: CParser Word16
 | 
			
		||||
_int16 = do
 | 
			
		||||
        ret <- lift $ do
 | 
			
		||||
                         a <- anyWord8 :: Parser Word8
 | 
			
		||||
@@ -40,7 +40,7 @@ _int16 = do
 | 
			
		||||
        return ret
 | 
			
		||||
 | 
			
		||||
-- | read a 32-Bit Int from Parsing-Input and log 4 bytes in our Parsing-Monad
 | 
			
		||||
int32 :: CParser Int32
 | 
			
		||||
int32 :: CParser Word32
 | 
			
		||||
int32 = do
 | 
			
		||||
        ret <- lift $ do
 | 
			
		||||
                         a <- anyWord8 :: Parser Word8
 | 
			
		||||
@@ -55,6 +55,7 @@ int32 = do
 | 
			
		||||
readHeader :: CParser IQMHeader
 | 
			
		||||
readHeader = do
 | 
			
		||||
         _ <- lift $ string (pack "INTERQUAKEMODEL\0")
 | 
			
		||||
         modify (+16)
 | 
			
		||||
         v <- int32
 | 
			
		||||
         -- when v /= 2 then --TODO: error something
 | 
			
		||||
         size' <- int32
 | 
			
		||||
@@ -85,7 +86,7 @@ readHeader = do
 | 
			
		||||
         ofs_extensions' <- int32
 | 
			
		||||
         return IQMHeader { version = v
 | 
			
		||||
                , filesize           = size'
 | 
			
		||||
                , flags              = flags'
 | 
			
		||||
                , flags              = fromIntegral flags'
 | 
			
		||||
                , num_text           = num_text'
 | 
			
		||||
                , ofs_text           = ofs_text'
 | 
			
		||||
                , num_meshes         = num_meshes'
 | 
			
		||||
@@ -140,6 +141,26 @@ readMeshes n = do
 | 
			
		||||
        ms <- readMeshes (n-1)
 | 
			
		||||
        return $ m:ms
 | 
			
		||||
 | 
			
		||||
-- | Parser for Mesh-Structure
 | 
			
		||||
readVAF :: CParser IQMVertexArray
 | 
			
		||||
readVAF = do
 | 
			
		||||
        vat <- rawEnumToVAT =<< int32
 | 
			
		||||
        flags' <- int32
 | 
			
		||||
        format <- rawEnumToVAF =<< int32
 | 
			
		||||
        size <- int32
 | 
			
		||||
        offset <- int32
 | 
			
		||||
        return $ IQMVertexArray vat (fromIntegral flags') format (fromIntegral size) offset
 | 
			
		||||
 | 
			
		||||
-- | helper to read n consecutive Meshes tail-recursive
 | 
			
		||||
readVAFs :: Int -> CParser [IQMVertexArray]
 | 
			
		||||
readVAFs 1 = do
 | 
			
		||||
        f <- readVAF
 | 
			
		||||
        return [f]
 | 
			
		||||
readVAFs n = do
 | 
			
		||||
        f <- readVAF
 | 
			
		||||
        fs <- readVAFs (n-1)
 | 
			
		||||
        return $ f:fs
 | 
			
		||||
 | 
			
		||||
-- | helper-Notation for subtracting 2 integral values of different kind in the precision
 | 
			
		||||
--   of the target-kind
 | 
			
		||||
(.-) :: forall a a1 a2.
 | 
			
		||||
@@ -171,9 +192,12 @@ parseIQM = do
 | 
			
		||||
        modify . (+) . fromIntegral $ num_text h                --put offset forward
 | 
			
		||||
        skipToCounter $ ofs_meshes h                            --skip 0-n bytes to get to meshes
 | 
			
		||||
        meshes' <- readMeshes (fromIntegral (num_meshes h))     --read meshes
 | 
			
		||||
        skipToCounter $ ofs_vertexarrays h                      --skip 0-n byots to get to vertexarray definition
 | 
			
		||||
        va <- readVAFs (fromIntegral (num_vertexarrays h))      --read them
 | 
			
		||||
        return IQM
 | 
			
		||||
                { header = h
 | 
			
		||||
                , texts = filter (not.null) (split (unsafeCoerce '\0') text)
 | 
			
		||||
                , meshes = meshes'
 | 
			
		||||
                , vertexArrays = va
 | 
			
		||||
                }
 | 
			
		||||
 | 
			
		||||
 
 | 
			
		||||
@@ -2,18 +2,26 @@
 | 
			
		||||
--   4-Byte in the documentation indicates Int32 - but not specified!
 | 
			
		||||
module Importer.IQM.Types where
 | 
			
		||||
 | 
			
		||||
import Control.Monad.Trans.State.Lazy (StateT)
 | 
			
		||||
import Data.Int
 | 
			
		||||
import Data.Word
 | 
			
		||||
import Data.ByteString
 | 
			
		||||
import Data.Attoparsec.ByteString.Char8
 | 
			
		||||
import Control.Monad.Trans.State.Lazy (StateT)
 | 
			
		||||
import Foreign.Ptr
 | 
			
		||||
import Graphics.Rendering.OpenGL.Raw.Types
 | 
			
		||||
import Prelude as P
 | 
			
		||||
 | 
			
		||||
-- | Mesh-Indices to distinguish the meshes referenced
 | 
			
		||||
newtype Mesh = Mesh Int32 deriving (Show, Eq)
 | 
			
		||||
newtype Mesh = Mesh Word32 deriving (Show, Eq)
 | 
			
		||||
-- | State-Wrapped Parser-Monad which is capable of counting the
 | 
			
		||||
--   Bytes read for offset-gap reasons
 | 
			
		||||
type CParser a = StateT Int64 Parser a
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
type Flags = GLbitfield      -- ^ Alias for UInt32
 | 
			
		||||
type Offset = Word32         -- ^ Alias for UInt32
 | 
			
		||||
type Index = GLuint          -- ^ Alias for UInt32
 | 
			
		||||
type NumComponents = GLsizei -- ^ Alias for UInt32
 | 
			
		||||
type IQMData = Ptr IQMVertexArrayFormat
 | 
			
		||||
 | 
			
		||||
-- | Header of IQM-Format.
 | 
			
		||||
--
 | 
			
		||||
@@ -23,33 +31,33 @@ type CParser a = StateT Int64 Parser a
 | 
			
		||||
--
 | 
			
		||||
--   ofs_* fields are aligned at 4-byte-boundaries
 | 
			
		||||
data IQMHeader = IQMHeader
 | 
			
		||||
                { version            :: Int32 -- ^ Must be 2
 | 
			
		||||
                , filesize           :: Int32
 | 
			
		||||
                , flags              :: Int32
 | 
			
		||||
                , num_text           :: Int32
 | 
			
		||||
                , ofs_text           :: Int32
 | 
			
		||||
                , num_meshes         :: Int32
 | 
			
		||||
                , ofs_meshes         :: Int32
 | 
			
		||||
                , num_vertexarrays   :: Int32
 | 
			
		||||
                , num_vertexes       :: Int32
 | 
			
		||||
                , ofs_vertexarrays   :: Int32
 | 
			
		||||
                , num_triangles      :: Int32
 | 
			
		||||
                , ofs_triangles      :: Int32
 | 
			
		||||
                , ofs_adjacency      :: Int32
 | 
			
		||||
                , num_joints         :: Int32
 | 
			
		||||
                , ofs_joints         :: Int32
 | 
			
		||||
                , num_poses          :: Int32
 | 
			
		||||
                , ofs_poses          :: Int32
 | 
			
		||||
                , num_anims          :: Int32
 | 
			
		||||
                , ofs_anims          :: Int32
 | 
			
		||||
                , num_frames         :: Int32
 | 
			
		||||
                , num_framechannels  :: Int32
 | 
			
		||||
                , ofs_frames         :: Int32
 | 
			
		||||
                , ofs_bounds         :: Int32
 | 
			
		||||
                , num_comment        :: Int32
 | 
			
		||||
                , ofs_comment        :: Int32
 | 
			
		||||
                , num_extensions     :: Int32 -- ^ stored as linked list, not as array.
 | 
			
		||||
                , ofs_extensions     :: Int32
 | 
			
		||||
                { version            :: Word32 -- ^ Must be 2
 | 
			
		||||
                , filesize           :: Word32
 | 
			
		||||
                , flags              :: Flags
 | 
			
		||||
                , num_text           :: Word32
 | 
			
		||||
                , ofs_text           :: Offset
 | 
			
		||||
                , num_meshes         :: Word32
 | 
			
		||||
                , ofs_meshes         :: Offset
 | 
			
		||||
                , num_vertexarrays   :: Word32
 | 
			
		||||
                , num_vertexes       :: Word32
 | 
			
		||||
                , ofs_vertexarrays   :: Offset
 | 
			
		||||
                , num_triangles      :: Word32
 | 
			
		||||
                , ofs_triangles      :: Offset
 | 
			
		||||
                , ofs_adjacency      :: Offset
 | 
			
		||||
                , num_joints         :: Word32
 | 
			
		||||
                , ofs_joints         :: Offset
 | 
			
		||||
                , num_poses          :: Word32
 | 
			
		||||
                , ofs_poses          :: Offset
 | 
			
		||||
                , num_anims          :: Word32
 | 
			
		||||
                , ofs_anims          :: Offset
 | 
			
		||||
                , num_frames         :: Word32
 | 
			
		||||
                , num_framechannels  :: Word32
 | 
			
		||||
                , ofs_frames         :: Offset
 | 
			
		||||
                , ofs_bounds         :: Offset
 | 
			
		||||
                , num_comment        :: Word32
 | 
			
		||||
                , ofs_comment        :: Offset
 | 
			
		||||
                , num_extensions     :: Word32 -- ^ stored as linked list, not as array.
 | 
			
		||||
                , ofs_extensions     :: Offset
 | 
			
		||||
                } deriving (Show, Eq)
 | 
			
		||||
 | 
			
		||||
-- | Format of an IQM-Mesh Structure.
 | 
			
		||||
@@ -57,11 +65,11 @@ data IQMHeader = IQMHeader
 | 
			
		||||
--   Read it like a Header of the Meshes lateron in the Format
 | 
			
		||||
data IQMMesh = IQMMesh
 | 
			
		||||
                { meshName              :: Maybe Mesh
 | 
			
		||||
                , meshMaterial          :: Int32
 | 
			
		||||
                , meshFirstVertex       :: Int32
 | 
			
		||||
                , meshNumVertexes       :: Int32
 | 
			
		||||
                , meshFirstTriangle     :: Int32
 | 
			
		||||
                , meshNumTriangles      :: Int32
 | 
			
		||||
                , meshMaterial          :: Word32
 | 
			
		||||
                , meshFirstVertex       :: Word32
 | 
			
		||||
                , meshNumVertexes       :: Word32
 | 
			
		||||
                , meshFirstTriangle     :: Word32
 | 
			
		||||
                , meshNumTriangles      :: Word32
 | 
			
		||||
                } deriving (Show, Eq)
 | 
			
		||||
 | 
			
		||||
-- | Format of a whole IQM-File
 | 
			
		||||
@@ -71,5 +79,95 @@ data IQM = IQM
 | 
			
		||||
        { header                :: IQMHeader
 | 
			
		||||
        , texts                 :: [ByteString]
 | 
			
		||||
        , meshes                :: [IQMMesh]
 | 
			
		||||
        , vertexArrays          :: [IQMVertexArray]
 | 
			
		||||
        } deriving (Show, Eq)
 | 
			
		||||
 | 
			
		||||
-- | Different Vertex-Array-Types in IQM
 | 
			
		||||
--
 | 
			
		||||
--   Custom Types have to be > 0x10 as of specification
 | 
			
		||||
 | 
			
		||||
data IQMVertexArrayType = IQMPosition
 | 
			
		||||
                       | IQMTexCoord
 | 
			
		||||
                       | IQMNormal
 | 
			
		||||
                       | IQMTangent
 | 
			
		||||
                       | IQMBlendIndexes
 | 
			
		||||
                       | IQMBlendWeights
 | 
			
		||||
                       | IQMColor
 | 
			
		||||
                       | IQMCustomVAT Word32
 | 
			
		||||
                       deriving (Show, Eq)
 | 
			
		||||
 | 
			
		||||
-- | Lookup-Function for internal enum to VertexArrayFormat
 | 
			
		||||
 | 
			
		||||
rawEnumToVAT :: Word32 -> CParser IQMVertexArrayType
 | 
			
		||||
rawEnumToVAT 0 = return IQMPosition
 | 
			
		||||
rawEnumToVAT 1 = return IQMTexCoord
 | 
			
		||||
rawEnumToVAT 2 = return IQMNormal
 | 
			
		||||
rawEnumToVAT 3 = return IQMTangent
 | 
			
		||||
rawEnumToVAT 4 = return IQMBlendIndexes
 | 
			
		||||
rawEnumToVAT 5 = return IQMBlendWeights
 | 
			
		||||
rawEnumToVAT 6 = return IQMColor
 | 
			
		||||
rawEnumToVAT a = return $ IQMCustomVAT a
 | 
			
		||||
 | 
			
		||||
-- | Vetrex-Array-Format of the data found at offset
 | 
			
		||||
data IQMVertexArrayFormat = IQMbyte
 | 
			
		||||
                            | IQMubyte
 | 
			
		||||
                            | IQMshort
 | 
			
		||||
                            | IQMushort
 | 
			
		||||
                            | IQMint
 | 
			
		||||
                            | IQMuint
 | 
			
		||||
                            | IQMhalf
 | 
			
		||||
                            | IQMfloat
 | 
			
		||||
                            | IQMdouble
 | 
			
		||||
--                            | Unknown Word32
 | 
			
		||||
                       deriving (Show, Eq)
 | 
			
		||||
 | 
			
		||||
-- | Lookup-Function for internal enum to VertexArrayFormat
 | 
			
		||||
 | 
			
		||||
rawEnumToVAF :: Word32 -> CParser IQMVertexArrayFormat
 | 
			
		||||
rawEnumToVAF 0 = return IQMbyte
 | 
			
		||||
rawEnumToVAF 1 = return IQMubyte
 | 
			
		||||
rawEnumToVAF 2 = return IQMshort
 | 
			
		||||
rawEnumToVAF 3 = return IQMushort
 | 
			
		||||
rawEnumToVAF 4 = return IQMint
 | 
			
		||||
rawEnumToVAF 5 = return IQMuint
 | 
			
		||||
rawEnumToVAF 6 = return IQMhalf
 | 
			
		||||
rawEnumToVAF 7 = return IQMfloat
 | 
			
		||||
rawEnumToVAF 8 = return IQMdouble
 | 
			
		||||
--rawEnumToVAF a = return $ Unknown a
 | 
			
		||||
rawEnumToVAF a = fail $ P.concat ["unrecognized enum(",show a,") in VertexArrayFormat"]
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
-- | A Vertex-Array-Definiton.
 | 
			
		||||
--
 | 
			
		||||
--   The Vertex starts at Offset and has num_vertexes * NumComponents entries.
 | 
			
		||||
--
 | 
			
		||||
--   All Vertex-Arrays seem to have the same number of components, just differ in Type, Format
 | 
			
		||||
--   and Flags
 | 
			
		||||
data IQMVertexArray = IQMVertexArray
 | 
			
		||||
                        IQMVertexArrayType
 | 
			
		||||
                        Flags
 | 
			
		||||
                        IQMVertexArrayFormat
 | 
			
		||||
                        NumComponents
 | 
			
		||||
                        Offset
 | 
			
		||||
                       deriving (Eq)
 | 
			
		||||
instance Show IQMVertexArray where
 | 
			
		||||
    show (IQMVertexArray t fl fo nc off) = "IQMVertexArray (Type: " ++ (show t) ++
 | 
			
		||||
                                                        ", Flags: " ++ (show fl) ++
 | 
			
		||||
                                                        ", Format: " ++ (show fo) ++
 | 
			
		||||
                                                        ", NumComponents: " ++ (show nc) ++
 | 
			
		||||
                                                        ", Offset: " ++ (show off) ++
 | 
			
		||||
                                                        ")"
 | 
			
		||||
 | 
			
		||||
-- | A triangle out of the Vertices at the Indexed Positions
 | 
			
		||||
data IQMTriangle = IQMTriangle Index Index Index
 | 
			
		||||
                       deriving (Show, Eq)
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
-- | From the IQM-Format-Description:
 | 
			
		||||
--
 | 
			
		||||
--   each value is the index of the adjacent triangle for edge 0, 1, and 2, where ~0 (= -1)
 | 
			
		||||
--   indicates no adjacent triangle indexes are relative to the iqmheader.ofs_triangles array
 | 
			
		||||
--   and span all meshes, where 0 is the first triangle, 1 is the second, 2 is the third, etc.
 | 
			
		||||
data IQMAdjacency = IQMAdjacency Index Index Index
 | 
			
		||||
                       deriving (Show, Eq)
 | 
			
		||||
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user