started iqm-parser
- can parse header - can parse initial texts - can parse mesh-structure - cannot parse everything else.
This commit is contained in:
parent
a642c78c32
commit
40e3b6ed4d
@ -16,6 +16,9 @@ executable Pioneers
|
|||||||
Map.Graphics,
|
Map.Graphics,
|
||||||
Map.Creation,
|
Map.Creation,
|
||||||
Map.StaticMaps,
|
Map.StaticMaps,
|
||||||
|
IQM.Types,
|
||||||
|
IQM.TestMain,
|
||||||
|
IQM.Parser,
|
||||||
Render.Misc,
|
Render.Misc,
|
||||||
Render.Render,
|
Render.Render,
|
||||||
Render.RenderObject,
|
Render.RenderObject,
|
||||||
@ -41,6 +44,7 @@ executable Pioneers
|
|||||||
lens >=4.0,
|
lens >=4.0,
|
||||||
SDL2 >= 0.1.0,
|
SDL2 >= 0.1.0,
|
||||||
time >=1.4.0,
|
time >=1.4.0,
|
||||||
GLUtil >= 0.7
|
GLUtil >= 0.7,
|
||||||
|
attoparsec >= 0.11.2
|
||||||
Default-Language: Haskell2010
|
Default-Language: Haskell2010
|
||||||
|
|
||||||
|
BIN
sample.iqm
Normal file
BIN
sample.iqm
Normal file
Binary file not shown.
132
src/Importer/IQM/Parser.hs
Normal file
132
src/Importer/IQM/Parser.hs
Normal file
@ -0,0 +1,132 @@
|
|||||||
|
module Importer.IQM.Parser where
|
||||||
|
|
||||||
|
import Importer.IQM.Types
|
||||||
|
import Data.Attoparsec.ByteString.Char8
|
||||||
|
import Data.Attoparsec.ByteString
|
||||||
|
import Data.Attoparsec
|
||||||
|
import Data.ByteString.Char8 (pack)
|
||||||
|
import Data.ByteString (split, null)
|
||||||
|
import Data.Word
|
||||||
|
import Data.Int
|
||||||
|
import Data.List (foldl1)
|
||||||
|
import Foreign.C.Types
|
||||||
|
import Unsafe.Coerce
|
||||||
|
|
||||||
|
import Prelude as P hiding (take, null)
|
||||||
|
|
||||||
|
w8Toint :: Integral a => a -> a -> a
|
||||||
|
w8Toint i add = 256*i + add
|
||||||
|
|
||||||
|
|
||||||
|
int16 :: Parser Int16
|
||||||
|
int16 = do
|
||||||
|
a <- anyWord8 :: Parser Word8
|
||||||
|
b <- anyWord8 :: Parser Word8
|
||||||
|
return $ foldl1 w8Toint $ map fromIntegral [b,a]
|
||||||
|
|
||||||
|
int32 :: Parser Int32
|
||||||
|
int32 = do
|
||||||
|
a <- anyWord8 :: Parser Word8
|
||||||
|
b <- anyWord8 :: Parser Word8
|
||||||
|
c <- anyWord8 :: Parser Word8
|
||||||
|
d <- anyWord8 :: Parser Word8
|
||||||
|
return $ foldl1 w8Toint $ map fromIntegral [d,c,b,a]
|
||||||
|
|
||||||
|
readHeader = do
|
||||||
|
string (pack "INTERQUAKEMODEL\0")
|
||||||
|
v <- int32
|
||||||
|
-- when v /= 2 then --TODO: error something
|
||||||
|
size <- 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
|
||||||
|
ofs_extensions <- int32
|
||||||
|
return (IQMHeader { version = v
|
||||||
|
, filesize = size
|
||||||
|
, flags = flags
|
||||||
|
, num_text = num_text
|
||||||
|
, ofs_text = ofs_text
|
||||||
|
, num_meshes = num_meshes
|
||||||
|
, ofs_meshes = ofs_meshes
|
||||||
|
, num_vertexarrays = num_vertexarrays
|
||||||
|
, num_vertexes = num_vertexes
|
||||||
|
, ofs_vertexarrays = ofs_vertexarrays
|
||||||
|
, num_triangles = num_triangles
|
||||||
|
, ofs_triangles = ofs_triangles
|
||||||
|
, ofs_adjacency = ofs_adjacency
|
||||||
|
, num_joints = num_joints
|
||||||
|
, ofs_joints = ofs_joints
|
||||||
|
, num_poses = num_poses
|
||||||
|
, ofs_poses = ofs_poses
|
||||||
|
, num_anims = num_anims
|
||||||
|
, ofs_anims = ofs_anims
|
||||||
|
, num_frames = num_frames
|
||||||
|
, num_framechannels = num_framechannels
|
||||||
|
, ofs_frames = ofs_frames
|
||||||
|
, ofs_bounds = ofs_bounds
|
||||||
|
, num_comment = num_comment
|
||||||
|
, ofs_comment = ofs_comment
|
||||||
|
, num_extensions = num_extensions
|
||||||
|
, ofs_extensions = ofs_extensions
|
||||||
|
}
|
||||||
|
, 16+27*4)
|
||||||
|
|
||||||
|
readMesh :: Parser IQMMesh
|
||||||
|
readMesh = do
|
||||||
|
name <- int32
|
||||||
|
mat <- int32
|
||||||
|
fv <- int32
|
||||||
|
nv <- int32
|
||||||
|
ft <- int32
|
||||||
|
nt <- int32
|
||||||
|
return IQMMesh
|
||||||
|
{ meshName = if name == 0 then Nothing else Just (Mesh name)
|
||||||
|
, meshMaterial = mat
|
||||||
|
, meshFirstVertex = fv
|
||||||
|
, meshNumVertexes = nv
|
||||||
|
, meshFirstTriangle = ft
|
||||||
|
, meshNumTriangles = nt
|
||||||
|
}
|
||||||
|
|
||||||
|
readMeshes :: Int -> Parser [IQMMesh]
|
||||||
|
readMeshes 1 = do
|
||||||
|
m <- readMesh
|
||||||
|
return [m]
|
||||||
|
readMeshes n = do
|
||||||
|
m <- readMesh
|
||||||
|
ms <- readMeshes (n-1)
|
||||||
|
return $ m:ms
|
||||||
|
|
||||||
|
parseIQM :: Parser IQM
|
||||||
|
parseIQM = do
|
||||||
|
(h,soFar) <- readHeader
|
||||||
|
take $ (fromIntegral (ofs_text h)) - soFar
|
||||||
|
text <- take $ fromIntegral $ num_text h
|
||||||
|
meshes <- readMeshes (fromIntegral (num_meshes h))
|
||||||
|
return IQM
|
||||||
|
{ header = h
|
||||||
|
, texts = filter (not.null) (split (unsafeCoerce '\0') text)
|
||||||
|
, meshes = meshes
|
||||||
|
}
|
||||||
|
|
60
src/Importer/IQM/Types.hs
Normal file
60
src/Importer/IQM/Types.hs
Normal file
@ -0,0 +1,60 @@
|
|||||||
|
module Importer.IQM.Types where
|
||||||
|
|
||||||
|
import Data.Int
|
||||||
|
import Data.ByteString
|
||||||
|
|
||||||
|
newtype Mesh = Mesh Int32 deriving (Show, Eq)
|
||||||
|
newtype CParser a = Parser (a, Int64)
|
||||||
|
|
||||||
|
-- Int32 or Int64 - depending on implementation. Format just specifies "uint".
|
||||||
|
-- 4-Byte indicates Int32
|
||||||
|
|
||||||
|
-- | ofs_* fields are relative tot he beginning of the iqmheader struct
|
||||||
|
-- ofs_* fields are set to 0 when data is empty
|
||||||
|
-- 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
|
||||||
|
} deriving (Show, Eq)
|
||||||
|
|
||||||
|
|
||||||
|
data IQMMesh = IQMMesh
|
||||||
|
{ meshName :: Maybe Mesh
|
||||||
|
, meshMaterial :: Int32
|
||||||
|
, meshFirstVertex :: Int32
|
||||||
|
, meshNumVertexes :: Int32
|
||||||
|
, meshFirstTriangle :: Int32
|
||||||
|
, meshNumTriangles :: Int32
|
||||||
|
} deriving (Show, Eq)
|
||||||
|
|
||||||
|
data IQM = IQM
|
||||||
|
{ header :: IQMHeader
|
||||||
|
, texts :: [ByteString]
|
||||||
|
, meshes :: [IQMMesh]
|
||||||
|
} deriving (Show, Eq)
|
||||||
|
|
@ -60,12 +60,21 @@ import Render.Render (initRendering,
|
|||||||
import UI.Callbacks
|
import UI.Callbacks
|
||||||
import UI.GUIOverlay
|
import UI.GUIOverlay
|
||||||
import Types
|
import Types
|
||||||
|
import Importer.IQM.Parser
|
||||||
|
import Data.Attoparsec.Char8 (parseTest)
|
||||||
|
import qualified Data.ByteString as B
|
||||||
|
|
||||||
--import ThirdParty.Flippers
|
--import ThirdParty.Flippers
|
||||||
|
|
||||||
import qualified Debug.Trace as D (trace)
|
import qualified Debug.Trace as D (trace)
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
|
testParser = do
|
||||||
|
B.readFile "sample.iqm" >>= parseTest parseIQM
|
||||||
|
|
||||||
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
SDL.withInit [InitVideo, InitAudio, InitEvents, InitTimer] $ do --also: InitNoParachute -> faster, without parachute!
|
SDL.withInit [InitVideo, InitAudio, InitEvents, InitTimer] $ do --also: InitNoParachute -> faster, without parachute!
|
||||||
|
Loading…
Reference in New Issue
Block a user