Merge branch 'iqm' into tessallation

This commit is contained in:
Nicole Dresselhaus 2014-04-26 17:16:47 +02:00
commit 5898df3682
2 changed files with 46 additions and 23 deletions

View File

@ -196,33 +196,47 @@ skipToCounter a = do
put d put d
-- | Parses an IQM-File and handles back the Haskell-Structure -- | Parses an IQM-File and handles back the Haskell-Structure
--
-- Does a 2-Pass-Parsing. Reads in Structure on first pass (O(n))and
-- fills the Structure in a 2nd Pass from Offsets (O(memcpy'd bytes)).
parseIQM :: String -> IO IQM parseIQM :: String -> IO IQM
parseIQM a = parseIQM a =
do do
f <- B.readFile a f <- B.readFile a
putStrLn "Before Parse:" -- Parse Headers/Offsets
putStrLn $ show f let result = parse doIQMparse f
putStrLn "Real Parse:" raw <- case result of
r <- return $ parse doIQMparse f
raw <- case r of
Done _ x -> return x Done _ x -> return x
y -> error $ show y y -> error $ show y
let ret = raw -- Fill Vertex-Arrays with data of Offsets
return ret let va = vertexArrays raw
va' <- mapM (readInVAO f) va
return $ raw {
vertexArrays = va'
}
readInVAO :: IQMVertexArray -> ByteString -> IO IQMVertexArray -- | Allocates memory for the Vertex-data and copies it over there
readInVAO (IQMVertexArray type' a format num offset ptr) d = -- from the given input-String
--
-- Note: The String-Operations are O(1), so only O(numberOfCopiedBytes)
-- is needed in term of computation.
readInVAO :: ByteString -> IQMVertexArray -> IO IQMVertexArray
readInVAO d (IQMVertexArray type' a format num offset ptr) =
do do
let let
byteLen = (fromIntegral num)*(vaSize format) byteLen = fromIntegral num * vaSize format
data' = skipDrop (fromIntegral offset) byteLen d data' = skipDrop (fromIntegral offset) byteLen d
when (not (ptr == nullPtr)) $ error $ "Error reading Vertex-Array: Double Read of " ++ show type' unless (ptr == nullPtr) $ error $ "Error reading Vertex-Array: Double Read of " ++ show type'
p <- mallocBytes byteLen p <- mallocBytes byteLen
putStrLn $ concat ["Allocating ", show byteLen, " Bytes at ", show p]
unsafeUseAsCString data' (\s -> copyBytes p s byteLen) unsafeUseAsCString data' (\s -> copyBytes p s byteLen)
p' <- unsafeCoerce p return $ IQMVertexArray type' a format num offset $ castPtr p
return (IQMVertexArray type' a format num offset p')
-- | Real internal Parser.
--
-- Consumes the String only once, thus in O(n). But all Data-Structures are
-- not allocated and copied. readInVAO has to be called on each one.
doIQMparse :: Parser IQM doIQMparse :: Parser IQM
doIQMparse = doIQMparse =
flip evalStateT 0 $ --evaluate parser with state starting at 0 flip evalStateT 0 $ --evaluate parser with state starting at 0
@ -235,8 +249,6 @@ doIQMparse =
meshes' <- readMeshes $ fromIntegral $ num_meshes h --read meshes meshes' <- readMeshes $ fromIntegral $ num_meshes h --read meshes
skipToCounter $ ofs_vertexarrays h --skip 0-n bytes to get to Vertex-Arrays skipToCounter $ ofs_vertexarrays h --skip 0-n bytes to get to Vertex-Arrays
vaf <- readVAFs $ fromIntegral $ num_vertexarrays h --read Vertex-Arrays vaf <- readVAFs $ fromIntegral $ num_vertexarrays h --read Vertex-Arrays
_ <- lift takeByteString
return IQM return IQM
{ header = h { header = h
, texts = filter (not.null) (split (unsafeCoerce '\0') text) , texts = filter (not.null) (split (unsafeCoerce '\0') text)
@ -244,5 +256,9 @@ doIQMparse =
, vertexArrays = vaf , vertexArrays = vaf
} }
-- | Helper-Function for Extracting a random substring out of a Bytestring
-- by the Offsets provided.
--
-- O(1).
skipDrop :: Int -> Int -> ByteString -> ByteString skipDrop :: Int -> Int -> ByteString -> ByteString
skipDrop a b= B.drop b . B.take a skipDrop a b= B.drop b . B.take a

View File

@ -1,4 +1,4 @@
{-# LANGUAGE ExistentialQuantification, RankNTypes, CPP, BangPatterns #-} -- {-# LANGUAGE ExistentialQuantification, RankNTypes, CPP, BangPatterns #-}
-- | Word32 or Word64 - depending on implementation. Format just specifies "uint". -- | Word32 or Word64 - depending on implementation. Format just specifies "uint".
-- 4-Byte in the documentation indicates Word32 - but not specified! -- 4-Byte in the documentation indicates Word32 - but not specified!
module Importer.IQM.Types where module Importer.IQM.Types where
@ -13,7 +13,6 @@ import Graphics.Rendering.OpenGL.Raw.Types
import Prelude as P import Prelude as P
import Foreign.Storable import Foreign.Storable
import Foreign.C.Types import Foreign.C.Types
import Foreign.Marshal.Array
-- | Mesh-Indices to distinguish the meshes referenced -- | Mesh-Indices to distinguish the meshes referenced
newtype Mesh = Mesh Word32 deriving (Show, Eq) newtype Mesh = Mesh Word32 deriving (Show, Eq)
@ -21,10 +20,19 @@ newtype Mesh = Mesh Word32 deriving (Show, Eq)
-- Bytes read for offset-gap reasons -- Bytes read for offset-gap reasons
type CParser a = StateT Int64 Parser a type CParser a = StateT Int64 Parser a
-- | Alias
type Flags = GLbitfield -- ^ Alias for UInt32 type Flags = GLbitfield -- ^ Alias for UInt32
-- | Alias
type Offset = Word32 -- ^ Alias for UInt32 type Offset = Word32 -- ^ Alias for UInt32
-- | Alias
type Index = GLuint -- ^ Alias for UInt32 type Index = GLuint -- ^ Alias for UInt32
-- | Alias
type NumComponents = GLsizei -- ^ Alias for UInt32 type NumComponents = GLsizei -- ^ Alias for UInt32
-- | Data-BLOB inside IQM
type IQMData = Ptr IQMVertexArrayFormat -- ^ Pointer for Data type IQMData = Ptr IQMVertexArrayFormat -- ^ Pointer for Data
-- | Header of IQM-Format. -- | Header of IQM-Format.
@ -105,7 +113,6 @@ data IQM = IQM
-- | Different Vertex-Array-Types in IQM -- | Different Vertex-Array-Types in IQM
-- --
-- Custom Types have to be > 0x10 as of specification -- Custom Types have to be > 0x10 as of specification
data IQMVertexArrayType = IQMPosition data IQMVertexArrayType = IQMPosition
| IQMTexCoord | IQMTexCoord
| IQMNormal | IQMNormal
@ -117,7 +124,6 @@ data IQMVertexArrayType = IQMPosition
deriving (Show, Eq) deriving (Show, Eq)
-- | Lookup-Function for internal enum to VertexArrayFormat -- | Lookup-Function for internal enum to VertexArrayFormat
rawEnumToVAT :: Word32 -> CParser IQMVertexArrayType rawEnumToVAT :: Word32 -> CParser IQMVertexArrayType
rawEnumToVAT 0 = return IQMPosition rawEnumToVAT 0 = return IQMPosition
rawEnumToVAT 1 = return IQMTexCoord rawEnumToVAT 1 = return IQMTexCoord
@ -141,6 +147,7 @@ data IQMVertexArrayFormat = IQMbyte
-- | Unknown Word32 -- | Unknown Word32
deriving (Show, Eq) deriving (Show, Eq)
-- | Get the Size (in Bytes) of the given IQMVertexArrayFormat-Struct
vaSize :: IQMVertexArrayFormat -> Int vaSize :: IQMVertexArrayFormat -> Int
vaSize IQMbyte = sizeOf (undefined :: CSChar) vaSize IQMbyte = sizeOf (undefined :: CSChar)
vaSize IQMubyte = sizeOf (undefined :: CUChar) vaSize IQMubyte = sizeOf (undefined :: CUChar)
@ -148,7 +155,7 @@ vaSize IQMshort = sizeOf (undefined :: CShort)
vaSize IQMushort = sizeOf (undefined :: CUShort) vaSize IQMushort = sizeOf (undefined :: CUShort)
vaSize IQMint = sizeOf (undefined :: CInt) vaSize IQMint = sizeOf (undefined :: CInt)
vaSize IQMuint = sizeOf (undefined :: CUInt) vaSize IQMuint = sizeOf (undefined :: CUInt)
vaSize IQMhalf = sizeOf (undefined :: Word16) --TODO: Find 16-Bit-Float-Datatype vaSize IQMhalf = sizeOf (undefined :: Word16) --TODO: Find 16-Bit-Float-Datatype FIXME!
vaSize IQMfloat = sizeOf (undefined :: CFloat) vaSize IQMfloat = sizeOf (undefined :: CFloat)
vaSize IQMdouble = sizeOf (undefined :: CDouble) vaSize IQMdouble = sizeOf (undefined :: CDouble)
@ -157,7 +164,6 @@ vaSize IQMdouble = sizeOf (undefined :: CDouble)
--mallocVArray IQMubyte n = mallocArray n :: IO (Ptr CUChar) --mallocVArray IQMubyte n = mallocArray n :: IO (Ptr CUChar)
-- | Lookup-Function for internal enum to VertexArrayFormat -- | Lookup-Function for internal enum to VertexArrayFormat
rawEnumToVAF :: Word32 -> CParser IQMVertexArrayFormat rawEnumToVAF :: Word32 -> CParser IQMVertexArrayFormat
rawEnumToVAF 0 = return IQMbyte rawEnumToVAF 0 = return IQMbyte
rawEnumToVAF 1 = return IQMubyte rawEnumToVAF 1 = return IQMubyte
@ -187,10 +193,11 @@ data IQMVertexArray = IQMVertexArray
IQMData IQMData
deriving (Eq) deriving (Eq)
instance Show IQMVertexArray where instance Show IQMVertexArray where
show (IQMVertexArray t fl fo nc off _) = "IQMVertexArray (Type: " ++ show t ++ show (IQMVertexArray t fl fo nc off dat) = "IQMVertexArray (Type: " ++ show t ++
", Flags: " ++ show fl ++ ", Flags: " ++ show fl ++
", Format: " ++ show fo ++ ", Format: " ++ show fo ++
", NumComponents: " ++ show nc ++ ", NumComponents: " ++ show nc ++
", Offset: " ++ show off ++ ", Offset: " ++ show off ++
", Data at: " ++ show dat ++
")" ")"