more iqm - not tested, but typechecks and builds.

This commit is contained in:
Nicole Dresselhaus 2014-04-25 23:58:20 +02:00
parent 0af848996a
commit e6a56b8409
2 changed files with 41 additions and 6 deletions

View File

@ -9,9 +9,9 @@ import Importer.IQM.Types
import Data.Attoparsec.ByteString.Char8 import Data.Attoparsec.ByteString.Char8
import Data.Attoparsec.ByteString import Data.Attoparsec.ByteString
import Data.Attoparsec.Binary import Data.Attoparsec.Binary
import Data.Attoparsec (parse, takeByteString)
import Data.ByteString.Char8 (pack) import Data.ByteString.Char8 (pack)
import Data.ByteString (split, null, ByteString) import Data.ByteString (split, null, ByteString)
import Data.ByteString.Unsafe (unsafeUseAsCString)
import qualified Data.ByteString as B import qualified Data.ByteString as B
import Data.Word import Data.Word
import Data.Int import Data.Int
@ -19,6 +19,9 @@ import Unsafe.Coerce
import Control.Monad.Trans.State import Control.Monad.Trans.State
import Control.Monad.Trans.Class import Control.Monad.Trans.Class
import Control.Monad import Control.Monad
import Foreign.Ptr
import Foreign.Marshal.Alloc
import Foreign.Marshal.Utils
import Prelude as P hiding (take, null) import Prelude as P hiding (take, null)
@ -159,7 +162,7 @@ readVAF = do
format <- rawEnumToVAF =<< w32leCParser format <- rawEnumToVAF =<< w32leCParser
size <- w32leCParser size <- w32leCParser
offset <- w32leCParser offset <- w32leCParser
return $ IQMVertexArray vat (fromIntegral flags') format (fromIntegral size) offset return $ IQMVertexArray vat (fromIntegral flags') format (fromIntegral size) offset nullPtr
-- | helper to read n consecutive Meshes tail-recursive -- | helper to read n consecutive Meshes tail-recursive
readVAFs :: Int -> CParser [IQMVertexArray] readVAFs :: Int -> CParser [IQMVertexArray]
@ -202,6 +205,19 @@ parseIQM a =
let ret = raw let ret = raw
return ret return ret
readInVAO :: IQMVertexArray -> ByteString -> IO IQMVertexArray
readInVAO (IQMVertexArray type' a format num offset ptr) d =
do
let
byteLen = (fromIntegral num)*(vaSize format)
data' = skipDrop (fromIntegral offset) byteLen d
when (not (ptr == nullPtr)) $ error $ "Error reading Vertex-Array: Double Read of " ++ show type'
p <- mallocBytes byteLen
unsafeUseAsCString data' (\s -> copyBytes p s byteLen)
p' <- unsafeCoerce p
return (IQMVertexArray type' a format num offset p')
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

View File

@ -1,4 +1,4 @@
{-# LANGUAGE 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
@ -11,6 +11,9 @@ import Data.Attoparsec.ByteString.Char8
import Foreign.Ptr import Foreign.Ptr
import Graphics.Rendering.OpenGL.Raw.Types import Graphics.Rendering.OpenGL.Raw.Types
import Prelude as P import Prelude as P
import Foreign.Storable
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)
@ -22,7 +25,7 @@ type Flags = GLbitfield -- ^ Alias for UInt32
type Offset = Word32 -- ^ Alias for UInt32 type Offset = Word32 -- ^ Alias for UInt32
type Index = GLuint -- ^ Alias for UInt32 type Index = GLuint -- ^ Alias for UInt32
type NumComponents = GLsizei -- ^ Alias for UInt32 type NumComponents = GLsizei -- ^ Alias for UInt32
type IQMData = Ptr IQMVertexArrayFormat type IQMData = Ptr IQMVertexArrayFormat -- ^ Pointer for Data
-- | Header of IQM-Format. -- | Header of IQM-Format.
-- --
@ -138,6 +141,21 @@ data IQMVertexArrayFormat = IQMbyte
-- | Unknown Word32 -- | Unknown Word32
deriving (Show, Eq) deriving (Show, Eq)
vaSize :: IQMVertexArrayFormat -> Int
vaSize IQMbyte = sizeOf (undefined :: CSChar)
vaSize IQMubyte = sizeOf (undefined :: CUChar)
vaSize IQMshort = sizeOf (undefined :: CShort)
vaSize IQMushort = sizeOf (undefined :: CUShort)
vaSize IQMint = sizeOf (undefined :: CInt)
vaSize IQMuint = sizeOf (undefined :: CUInt)
vaSize IQMhalf = sizeOf (undefined :: Word16) --TODO: Find 16-Bit-Float-Datatype
vaSize IQMfloat = sizeOf (undefined :: CFloat)
vaSize IQMdouble = sizeOf (undefined :: CDouble)
--mallocVArray :: Storable a => IQMVertexArrayFormat -> Int -> IO (Ptr a)
--mallocVArray IQMbyte n = mallocArray n :: IO (Ptr CSChar)
--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
@ -166,9 +184,10 @@ data IQMVertexArray = IQMVertexArray
IQMVertexArrayFormat IQMVertexArrayFormat
NumComponents NumComponents
Offset Offset
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 _) = "IQMVertexArray (Type: " ++ show t ++
", Flags: " ++ show fl ++ ", Flags: " ++ show fl ++
", Format: " ++ show fo ++ ", Format: " ++ show fo ++
", NumComponents: " ++ show nc ++ ", NumComponents: " ++ show nc ++