haddock for iqm (so far) complete
This commit is contained in:
parent
ae5ea60d65
commit
dc0ed4770a
@ -1,6 +1,9 @@
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
|
||||
module Importer.IQM.Parser where
|
||||
-- | Parser for IQM-Files
|
||||
--
|
||||
-- Assumes that the file is stored with 32-Bit-BigEndian-Ints
|
||||
module Importer.IQM.Parser (parseIQM) where
|
||||
|
||||
import Importer.IQM.Types
|
||||
import Data.Attoparsec.ByteString.Char8
|
||||
@ -16,14 +19,19 @@ import Control.Monad
|
||||
|
||||
import Prelude as P hiding (take, null)
|
||||
|
||||
-- | helper-function for creating an integral out of [8-Bit Ints]
|
||||
w8ToInt :: Integral a => a -> a -> a
|
||||
w8ToInt i add = 256*i + add
|
||||
|
||||
-- | shorthand-function for parsing Word8 into Integrals
|
||||
parseNum :: (Integral a, Integral b) => [a] -> b
|
||||
parseNum = (foldl1 w8ToInt) . map fromIntegral
|
||||
|
||||
int16 :: CParser Int16
|
||||
int16 = do
|
||||
-- | 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 = do
|
||||
ret <- lift $ do
|
||||
a <- anyWord8 :: Parser Word8
|
||||
b <- anyWord8 :: Parser Word8
|
||||
@ -31,6 +39,7 @@ int16 = do
|
||||
modify (+2)
|
||||
return ret
|
||||
|
||||
-- | read a 32-Bit Int from Parsing-Input and log 4 bytes in our Parsing-Monad
|
||||
int32 :: CParser Int32
|
||||
int32 = do
|
||||
ret <- lift $ do
|
||||
@ -42,6 +51,7 @@ int32 = do
|
||||
modify (+4)
|
||||
return $ ret
|
||||
|
||||
-- | Parser for the header
|
||||
readHeader :: CParser IQMHeader
|
||||
readHeader = do
|
||||
_ <- lift $ string (pack "INTERQUAKEMODEL\0")
|
||||
@ -102,6 +112,7 @@ readHeader = do
|
||||
, ofs_extensions = ofs_extensions'
|
||||
}
|
||||
|
||||
-- | Parser for Mesh-Structure
|
||||
readMesh :: CParser IQMMesh
|
||||
readMesh = do
|
||||
name <- int32
|
||||
@ -119,6 +130,7 @@ readMesh = do
|
||||
, meshNumTriangles = nt
|
||||
}
|
||||
|
||||
-- | helper to read n consecutive Meshes tail-recursive
|
||||
readMeshes :: Int -> CParser [IQMMesh]
|
||||
readMeshes 1 = do
|
||||
m <- readMesh
|
||||
@ -128,6 +140,8 @@ readMeshes n = do
|
||||
ms <- readMeshes (n-1)
|
||||
return $ m:ms
|
||||
|
||||
-- | helper-Notation for subtracting 2 integral values of different kind in the precision
|
||||
-- of the target-kind
|
||||
(.-) :: forall a a1 a2.
|
||||
(Num a, Integral a2, Integral a1) =>
|
||||
a1 -> a2 -> a
|
||||
@ -135,21 +149,26 @@ readMeshes n = do
|
||||
|
||||
infix 5 .-
|
||||
|
||||
-- | skips (=drops) all input until the internal counter is at a given bytecount
|
||||
--
|
||||
-- Fails the parser if given bytecount is lower than the internal counter as we
|
||||
-- read sequentially and do not do backtracking
|
||||
skipToCounter :: Integral a => a -> CParser ()
|
||||
skipToCounter a = do
|
||||
let d = fromIntegral a
|
||||
c <- get
|
||||
c <- get
|
||||
when (d < c) $ fail "wanting to skip to counter already passed"
|
||||
_ <- lift $ take $ d .- c
|
||||
put d
|
||||
_ <- lift $ take $ d .- c
|
||||
put d
|
||||
|
||||
-- | Parses an IQM-File and handles back the Haskell-Structure
|
||||
parseIQM :: CParser IQM
|
||||
parseIQM = do
|
||||
put 0 --start at offset 0
|
||||
h <- readHeader --read header
|
||||
skipToCounter $ ofs_text h --skip 0-n bytes to get to text
|
||||
put 0 --start at offset 0
|
||||
h <- readHeader --read header
|
||||
skipToCounter $ ofs_text h --skip 0-n bytes to get to text
|
||||
text <- lift . take . fromIntegral $ num_text h --read texts
|
||||
modify . (+) . fromIntegral $ num_text h --put offset forward
|
||||
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
|
||||
return IQM
|
||||
|
Loading…
Reference in New Issue
Block a user