Skip to content

Commit

Permalink
Fix AssetLoaders
Browse files Browse the repository at this point in the history
Fix Asset loaders to load GLTFs
  • Loading branch information
MilesLitteral committed Mar 20, 2024
1 parent 0580681 commit 1912bcf
Show file tree
Hide file tree
Showing 7 changed files with 211 additions and 212 deletions.
4 changes: 2 additions & 2 deletions hraylib3d.cabal
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
cabal-version: 1.12

-- This file has been generated from package.yaml by hpack version 0.34.4.
-- This file has been generated from package.yaml by hpack version 0.35.2.
--
-- see: https://github.com/sol/hpack

Expand Down Expand Up @@ -82,7 +82,7 @@ library
HRayLib3d.GameEngine.Loader.Entity
HRayLib3d.GameEngine.Loader.GameCharacter
HRayLib3d.GameEngine.Loader.GLB
HRayLib3d.GameEngine.Loader.GLTF
HRayLib3d.GameEngine.Loader.GlTF
HRayLib3d.GameEngine.Loader.Image
HRayLib3d.GameEngine.Loader.MD3
HRayLib3d.GameEngine.Loader.ShaderParser
Expand Down
2 changes: 2 additions & 0 deletions src/HRayLib3d/GameEngine/Data/AssetIR.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
module HRayLib3d.GameEngine.Data.AssetIR where

68 changes: 33 additions & 35 deletions src/HRayLib3d/GameEngine/Graphics/GLTF.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,8 @@ module HRayLib3d.GameEngine.Graphics.GLTF

import Foreign ( Ptr, Storable, castPtr )
import Data.Map ( Map )
import Data.Aeson ( eitherDecodeFileStrict )
import Data.Maybe ( fromJust )
import Data.Aeson ( (.:), withObject, eitherDecodeFileStrict, FromJSON, decode, Value )
import Data.Maybe ( fromJust, fromMaybe )
import Data.Vector ( Vector )
import Data.HashSet ( HashSet )
import Data.Text.Unsafe ( inlinePerformIO )
Expand All @@ -35,13 +35,15 @@ import Codec.GlTF.BufferView ( BufferView(..) )
import Codec.GlTF.Texture ()
import Codec.GlTF.URI ( loadURI, URI )

import LambdaCube.GL ( ArrayType (ArrWord32), Buffer, BufferSetter(..), Stream(..), Object(..), IndexStream(..), updateBuffer, Array(..), GLStorage(..), ArrayType (ArrFloat), compileBuffer, addObject, Primitive (TriangleList), V4 (..), V2 (..) )
import LambdaCube.GL ( ArrayType (..), Buffer, Stream(..), Object(..), IndexStream(..), updateBuffer, Array(..), GLStorage(..), ArrayType (ArrFloat), compileBuffer, addObject, Primitive (TriangleList), V4 (..), V2 (..) )
import LambdaCube.GL.Mesh ( addMeshToObjectArray, uploadMeshToGPU )
import HRayLib3d.GameEngine.Data.GLTF ( GLTFModel(..) )
import HRayLib3d.GameEngine.Graphics.Storage ( addObjectWithMaterial )
import HRayLib3d.GameEngine.Utils ( bbox, setNub, sphere )
import LambdaCube.PipelineSchema ( StreamType(..) )
import qualified Codec.GlTF.Material as Material
import Data.Vect.Float.Base (Vec3(..))
import Data.Aeson.Types (FromJSON(parseJSON))

data GlTFInstance
= GlTFInstance
Expand Down Expand Up @@ -70,11 +72,9 @@ decodeBase64 bs = case B64.decode bs of
--B64.decode bs >>= return . SB8.dropWhile (== '\NUL')

procRawBytes :: Codec.GlTF.URI.URI -> IO T.Text
procRawBytes uriBytes = do
rawURIBytes <- loadURI eitherDecodeFileStrict uriBytes
case rawURIBytes of
Left _ -> error "Bad URI"
Right a -> return (T.pack $ show a)
procRawBytes uriBytes = do return $ T.pack . show $ uriBytes

instance (Num ComponentType)

-- Type GlTF.BufferView was BL.ByteString before
extractData :: Codec.GlTF.Buffer.Buffer -> Codec.GlTF.Accessor.Accessor -> Codec.GlTF.BufferView.BufferView -> Maybe [Float]
Expand Down Expand Up @@ -126,21 +126,24 @@ cvtGlTF Codec.GlTF.GlTF{..} = do
--bufferViewIndex = bufferViewIx -- Choose the desired buffer view index
-- encodedData = C8.dropWhile (/= ',') (C8.pack $ URI $ fromJust uri) (C8.unpack encodedData)
if "data:application/octet-stream;base64," `SB8.isPrefixOf` SB8.pack dataMaybe
then processGLTF gBuffers gAccessors bufferViewIxs
then processGLTF gBuffers gAccessors bufferViewIxs
else error "Bad Data URI"

processGLTF :: Vector Codec.GlTF.Buffer.Buffer -> Vector Accessor -> Vector BufferView -> (Array, Array, Vector (Array, Array))
processGLTF gBuffers gAccessors bufferViewIxs = do
let indices = fromJust $ extractData (gBuffers V.! 4) (gAccessors V.! 4) (bufferViewIxs V.! 4)
normals = fromJust $ extractData (gBuffers V.! 1) (gAccessors V.! 1) (bufferViewIxs V.! 1)
texCoords = fromJust $ extractData (gBuffers V.! 3) (gAccessors V.! 3) (bufferViewIxs V.! 3)
return (Array (ArrWord32 (SV.length $ SV.fromList indices) (withV $ SV.fromList indices)), Array (ArrFloat (2 * SV.length (SV.fromList texCoords)) (withV (V.fromList texCoords))), V.map cvtPosNorm (V.fromList normals))
ar1 = Array ArrFloat (SV.length $ SV.fromList indices) (withV $ SV.fromList indices)
ar2 = Array ArrFloat (2 * SV.length (SV.fromList texCoords)) (withV $ SV.fromList texCoords)
vb = V.map cvtPosNorm (V.fromList [(SV.fromList texCoords, SV.fromList normals)])
(ar1, ar2, vb)

withV :: Storable a => SV.Vector a -> (Ptr b1 -> IO b2) -> IO b2
withV a f = SV.unsafeWith a (\p -> f $ castPtr p)

cvtPosNorm :: (SV.Vector a1, SV.Vector a2) -> (Int -> BufferSetter -> Array, Int -> BufferSetter -> Array)
cvtPosNorm (p,n) = (f p, f n) where f sv = Array $ ArrFloat (3 * SV.length sv) $ withV sv
cvtPosNorm :: Storable a => (SV.Vector a, SV.Vector a) -> (Array, Array) -- (Int -> BufferSetter -> Array, Int -> BufferSetter -> Array)
cvtPosNorm (p,n) = (f p, f n) where f sv = Array ArrFloat (3 * SV.length sv) $ withV sv

addSurface :: GlTF -> ([Array], [Array], [Array], [Array], [Vector (Array, Array)]) -> ([Array], [Array], [Array], [Array], [Vector (Array, Array)])
addSurface sf (il,tl,pl,nl,pnl) = do
Expand All @@ -153,10 +156,10 @@ uploadGlTF :: GLTFModel -> IO GPUGlTF
uploadGlTF model = do
let (il, tl, pl, nl, pnl) = addSurface (gltfRaw model) ([],[],[],[],[])
buffer <- compileBuffer (concat [il, tl, pl, nl])
let numSurfaces = V.length gltfSurfaces
surfaceData idx GLTFModel{..} = (index,attributes) where
index = IndexStream buffer idx 0 (SV.length srGlTFTriangles)
countV = SV.length srGlTFTexCoords
let numSurfaces = length il -- / 4) -- TODO: a Let to properly support GlTF animations
surfaceData idx GLTFModel{..} = (index, attributes) where
index = IndexStream buffer idx 0 (length tl)
countV = length pl
attributes = Map.fromList
[ ("diffuseUV", Stream Attribute_V2F buffer (1 * numSurfaces + idx) 0 countV)
, ("position", Stream Attribute_V3F buffer (2 * numSurfaces + idx) 0 countV)
Expand All @@ -165,36 +168,31 @@ uploadGlTF model = do
, ("lightmapUV", ConstV2F (V2 0 0))
]
frames = Prelude.foldr addSurfaceFrames emptyFrame $ zip [0..] pnl where
emptyFrame = V.replicate (V.length gltfFrames) []
emptyFrame = V.replicate 0 [] --gltfFrames
addSurfaceFrames (idx,pn) f = V.zipWith (\l (p,n) -> (2 * numSurfaces + idx,p):(3 * numSurfaces + idx,n):l) f pn
return $ GPUGlTF
{ gpuGlTFBuffer = buffer
, gpuGlTFSurfaces = zipWith surfaceData [0..] (V.toList gltfSurfaces)
, gpuGlTFSurfaces = zipWith surfaceData [0..] [model] --(V.fromList gltfSurfaces)
, gpuGlTFFrames = frames
, gpuGlTFModel = model
, gpuGlTFShaders = HashSet.fromList $ concat [map (T.unpack . fromJust . Material.name) $ V.toList gpuGlTFShaders | GLTFModel{..} <- V.toList gltfRaw]
}
, gpuGlTFShaders = HashSet.fromList $ concat [[] | GLTFModel{..} <- [model]] -- [map (T.unpack . fromJust . Material.name) $ listOfMat | GLTFModel{..} <- V.toList gltfRaw]]
} --V.toList gpuGlTFShaders

addGPUGlTF :: GLStorage -> GPUGlTF -> [String] -> IO GlTFInstance
addGPUGlTF r GPUGlTF{..} unis = do
let GlTF{..} = gltfRaw gpuGlTFModel
objs <- V.forM (zip gpuGlTFSurfaces $ V.toList gltfSurfaces) $ \((index,attrs),sf) -> do
let materialName s = case Map.lookup (Material.name sf) skins of
Nothing -> Material.name s
Just a -> a
objList <- concat <$> V.forM (V.fromList $ Codec.GlTF.extensions sf) (\s -> do
a <- addObjectWithMaterial r (T.unpack . fromJust $ materialName s) TriangleList (Just index) attrs $ setNub $ "worldMat":unis
b <- addObject r "LightMapOnly" TriangleList (Just index) attrs $ setNub $ "worldMat":unis
return [a,b])
objs <- V.forM (V.fromList gpuGlTFSurfaces) $ \(index, _) -> do
objList <- concat <$> V.forM (V.fromList [fromMaybe Codec.GlTF.extensions]) (\_ -> do
a <- addObjectWithMaterial r (T.unpack . fromJust $ Material.name (fromJust materials V.! 1)) TriangleList (Just index) Map.empty $ setNub $ "worldMat":unis
b <- addObject r "LightMapOnly" TriangleList (Just index) Map.empty $ setNub $ "worldMat":unis
return [a,b]) --attrs

-- add collision geometry
collisionObjs <- case V.fromList objList of
(GlTF{..}:_) -> do
sphereObj <- uploadMeshToGPU (sphere (V4 1 0 0 1) 4 radius) >>= addMeshToObjectArray r "CollisionShape" (setNub $ ["worldMat","origin"] ++ unis)
boxObj <- uploadMeshToGPU (bbox (V4 0 0 1 1) Codec.GlTF.Accessor.min Codec.GlTF.Accessor.max) >>= addMeshToObjectArray r "CollisionShape" (setNub $ ["worldMat","origin"] ++ unis)
--when (frOrigin /= zero) $ putStrLn $ "frOrigin: " ++ show frOrigin
return [sphereObj,boxObj]
_ -> return []
collisionObjs <- do --TODO: re-add radius
sphereObj <- uploadMeshToGPU (sphere (V4 1 0 0 1) 4 1.0) >>= addMeshToObjectArray r "CollisionShape" (setNub $ ["worldMat","origin"] ++ unis)
boxObj <- uploadMeshToGPU (bbox (V4 0 0 1 1) (Vec3 0 0 0) {- Codec.GlTF.Accessor.min -} (Vec3 0 0 0) {- Codec.GlTF.Accessor.max -}) >>= addMeshToObjectArray r "CollisionShape" (setNub $ ["worldMat","origin"] ++ unis)
--when (frOrigin /= zero) $ putStrLn $ "frOrigin: " ++ show frOrigin
return [sphereObj,boxObj]
return $ objList ++ collisionObjs
-- question: how will be the referred shaders loaded?
-- general problem: should the gfx network contain all passes (every possible materials)?
Expand Down
2 changes: 1 addition & 1 deletion src/HRayLib3d/GameEngine/Graphics/OBJ.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE FlexibleInstances, RecordWildCards #-}
module HRayLib3d.GameEngine.Graphics.OBJ
( addOBJ
, addGPUOBJ
Expand Down
36 changes: 18 additions & 18 deletions src/HRayLib3d/GameEngine/Loader.hs
Original file line number Diff line number Diff line change
@@ -1,21 +1,21 @@
module HRayLib3d.GameEngine.Loader (
-- module HRayLib3d.GameEngine.Loader.BSP,
-- module HRayLib3d.GameEngine.Loader.Entity,
-- module HRayLib3d.GameEngine.Loader.GameCharacter,
-- module HRayLib3d.GameEngine.Loader.GLB,
-- module HRayLib3d.GameEngine.Loader.GlTF,
-- module HRayLib3d.GameEngine.Loader.Image,
-- module HRayLib3d.GameEngine.Loader.MD3,
-- module HRayLib3d.GameEngine.Loader.ShaderParser,
-- module HRayLib3d.GameEngine.Loader.Zip
module HRayLib3d.GameEngine.Loader.BSP,
module HRayLib3d.GameEngine.Loader.Entity,
module HRayLib3d.GameEngine.Loader.GameCharacter,
module HRayLib3d.GameEngine.Loader.GLB,
module HRayLib3d.GameEngine.Loader.GlTF,
module HRayLib3d.GameEngine.Loader.Image,
module HRayLib3d.GameEngine.Loader.MD3,
module HRayLib3d.GameEngine.Loader.ShaderParser,
module HRayLib3d.GameEngine.Loader.Zip
) where

-- import HRayLib3d.GameEngine.Loader.BSP,
-- import HRayLib3d.GameEngine.Loader.Entity,
-- import HRayLib3d.GameEngine.Loader.GameCharacter,
-- import HRayLib3d.GameEngine.Loader.GLB,
-- import HRayLib3d.GameEngine.Loader.GlTF,
-- import HRayLib3d.GameEngine.Loader.Image,
-- import HRayLib3d.GameEngine.Loader.MD3,
-- import HRayLib3d.GameEngine.Loader.ShaderParser,
-- import HRayLib3d.GameEngine.Loader.Zip
import HRayLib3d.GameEngine.Loader.BSP
import HRayLib3d.GameEngine.Loader.Entity
import HRayLib3d.GameEngine.Loader.GameCharacter
import HRayLib3d.GameEngine.Loader.GLB
import HRayLib3d.GameEngine.Loader.GlTF
import HRayLib3d.GameEngine.Loader.Image
import HRayLib3d.GameEngine.Loader.MD3
import HRayLib3d.GameEngine.Loader.ShaderParser
import HRayLib3d.GameEngine.Loader.Zip
2 changes: 1 addition & 1 deletion src/HRayLib3d/GameEngine/Loader/GLTF.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE OverloadedStrings, ViewPatterns #-}
module HRayLib3d.GameEngine.Loader.GLTF
module HRayLib3d.GameEngine.Loader.GlTF
( readGLTF
, loadGLTF
, getGLTFModel
Expand Down
Loading

0 comments on commit 1912bcf

Please sign in to comment.