summaryrefslogtreecommitdiff
path: root/LoadMesh.hs
diff options
context:
space:
mode:
authorJoe Crayne <joe@jerkface.net>2019-06-18 00:35:19 -0400
committerJoe Crayne <joe@jerkface.net>2019-06-18 00:35:19 -0400
commit811dec27f1ca7eedca4dc25c100da51659639c8f (patch)
tree6bdee51fc2040519f192701699e7263f6e7431f4 /LoadMesh.hs
parent40b339a401a82610d16601e9a1ce34af9b159d56 (diff)
Materials and textures are relative to object file.
Diffstat (limited to 'LoadMesh.hs')
-rw-r--r--LoadMesh.hs36
1 files changed, 21 insertions, 15 deletions
diff --git a/LoadMesh.hs b/LoadMesh.hs
index 9eaa047..ee93344 100644
--- a/LoadMesh.hs
+++ b/LoadMesh.hs
@@ -3,11 +3,12 @@
3{-# LANGUAGE FlexibleContexts #-} 3{-# LANGUAGE FlexibleContexts #-}
4module LoadMesh where 4module LoadMesh where
5 5
6import LambdaCube.GL as LambdaCubeGL -- renderer 6import LambdaCube.GL as LC -- renderer
7import LambdaCube.GL.Mesh as LambdaCubeGL 7import LambdaCube.GL.Mesh as LambdaCubeGL
8import MtlParser 8import MtlParser
9 9
10import Control.Monad 10import Control.Monad
11import Data.Int
11import Data.Maybe 12import Data.Maybe
12import Data.Map (Map) 13import Data.Map (Map)
13import qualified Data.Map as Map 14import qualified Data.Map as Map
@@ -16,7 +17,8 @@ import qualified Data.ByteString as SB
16import qualified Data.ByteString.Lazy.Char8 as L 17import qualified Data.ByteString.Lazy.Char8 as L
17import Data.Text (unpack,Text) 18import Data.Text (unpack,Text)
18import Data.List (groupBy,nub) 19import Data.List (groupBy,nub)
19import Numeric.LinearAlgebra hiding ((<>)) 20import Numeric.LinearAlgebra hiding ((<>),Element)
21import System.FilePath
20 22
21import Codec.Picture as Juicy 23import Codec.Picture as Juicy
22import Wavefront 24import Wavefront
@@ -24,15 +26,20 @@ import Wavefront.Types
24import Data.Aeson 26import Data.Aeson
25 27
26type MeshData = ( [(Mesh,Maybe Text)] -- List of uniform-material meshes (and the name of the material). 28type MeshData = ( [(Mesh,Maybe Text)] -- List of uniform-material meshes (and the name of the material).
27 , MtlLib -- Material definitions. 29 , ( MtlLib -- Material definitions.
30 , FilePath ) -- Path to wavefront obj file.
28 ) 31 )
29 32
33relativeFrom :: FilePath -> FilePath -> FilePath
34relativeFrom path file | isAbsolute file = file
35relativeFrom path file = takeDirectory path </> file
36
30loadOBJ :: String -> IO (Either String MeshData) 37loadOBJ :: String -> IO (Either String MeshData)
31loadOBJ fname = L.readFile fname >>= \bs -> do 38loadOBJ fname = L.readFile fname >>= \bs -> do
32 let obj@OBJ{..} = parse bs 39 let obj@OBJ{..} = parse bs
33 -- load materials 40 -- load materials
34 mtlLib <- mconcat . V.toList <$> mapM (readMtl . unpack) objMtlLibs 41 mtlLib <- mconcat . V.toList <$> mapM (readMtlWithFallback . relativeFrom fname . unpack) objMtlLibs
35 return $ Right (objToMesh obj,mtlLib) 42 return $ Right (objToMesh obj,(mtlLib,fname))
36 43
37 44
38data BoundingBox = BoundingBox 45data BoundingBox = BoundingBox
@@ -99,25 +106,25 @@ transformMesh t m = m
99 { mAttributes = Map.adjust (tranformAttribute t) "position" (mAttributes m) 106 { mAttributes = Map.adjust (tranformAttribute t) "position" (mAttributes m)
100 } 107 }
101 108
102uploadOBJToGPU :: Maybe BoundingBox -> MeshData -> IO (([(GPUMesh, Maybe Text)], MtlLib),Matrix Float) 109uploadOBJToGPU :: Maybe BoundingBox -> MeshData -> IO ([(GPUMesh, Maybe Text)],Matrix Float)
103uploadOBJToGPU scalebb (subModels,mtlLib) = do 110uploadOBJToGPU scalebb (subModels,(mtlLib,objpath)) = do
104 let meshbb = foldMap (attribBoundingBox . mAttributes . fst) subModels :: BoundingBox 111 let meshbb = foldMap (attribBoundingBox . mAttributes . fst) subModels :: BoundingBox
105 m = maybe (ident 4) (scaleWithin meshbb) scalebb 112 m = maybe (ident 4) (scaleWithin meshbb) scalebb
106 gpuSubModels <- forM subModels $ \(mesh,mat) -> LambdaCubeGL.uploadMeshToGPU (transformMesh m mesh) >>= \a -> return (a,mat) 113 gpuSubModels <- forM subModels $ \(mesh,mat) -> LambdaCubeGL.uploadMeshToGPU (transformMesh m mesh) >>= \a -> return (a,mat)
107 return ((gpuSubModels,mtlLib),m) 114 return (gpuSubModels,m)
108 115
109uploadMtlLib :: MtlLib -> IO (Map Text (ObjMaterial,TextureData)) 116uploadMtlLib :: (MtlLib,FilePath) -> IO (Map Text (ObjMaterial,TextureData))
110uploadMtlLib mtlLib = do 117uploadMtlLib (mtlLib,objpath) = do
111 -- collect used textures 118 -- collect used textures
112 let usedTextures = nub . concatMap (maybeToList . mtl_map_Kd) $ Map.elems mtlLib 119 let usedTextures = nub . concatMap (maybeToList . mtl_map_Kd) $ Map.elems mtlLib
113 whiteImage = Juicy.ImageRGB8 $ Juicy.generateImage (\_ _ -> Juicy.PixelRGB8 255 255 255) 1 1 120 whiteImage = Juicy.ImageRGB8 $ Juicy.generateImage (\_ _ -> Juicy.PixelRGB8 255 255 255) 1 1
114 checkerImage = Juicy.ImageRGB8 $ Juicy.generateImage (\x y -> if mod (x + y) 2 == 0 then Juicy.PixelRGB8 0 0 0 else Juicy.PixelRGB8 255 255 0) 2 2 121 checkerImage = Juicy.ImageRGB8 $ Juicy.generateImage (\x y -> if mod (x + y) 2 == 0 then Juicy.PixelRGB8 0 0 0 else Juicy.PixelRGB8 255 255 0) 2 2
115 checkerTex <- LambdaCubeGL.uploadTexture2DToGPU checkerImage 122 checkerTex <- LC.uploadTexture2DToGPU checkerImage
116 -- load images and upload to gpu 123 -- load images and upload to gpu
117 textureLib <- forM (Map.fromList $ zip usedTextures usedTextures) $ \fname -> Juicy.readImage fname >>= \case 124 textureLib <- forM (Map.fromList $ zip usedTextures usedTextures) $ \fname -> Juicy.readImage (relativeFrom objpath fname) >>= \case
118 Left err -> putStrLn (fname ++": "++err) >> return checkerTex 125 Left err -> putStrLn (fname ++": "++err) >> return checkerTex
119 Right img -> LambdaCubeGL.uploadTexture2DToGPU img 126 Right img -> LC.uploadTexture2DToGPU img
120 whiteTex <- LambdaCubeGL.uploadTexture2DToGPU whiteImage 127 whiteTex <- LC.uploadTexture2DToGPU whiteImage
121 -- pair textures and materials 128 -- pair textures and materials
122 return $ (\a -> (a, maybe whiteTex (fromMaybe checkerTex . flip Map.lookup textureLib) . mtl_map_Kd $ a)) <$> mtlLib 129 return $ (\a -> (a, maybe whiteTex (fromMaybe checkerTex . flip Map.lookup textureLib) . mtl_map_Kd $ a)) <$> mtlLib
123 130
@@ -144,4 +151,3 @@ objToMesh OBJ{..} = [(toMesh faceGroup, elMtl . head $ faceGroup) | faceGroup <-
144 , let TexCoord x y z = fromMaybe defaultTexCoord ((objTexCoords !-) =<< faceTexCoordIndex) in V3 x y z 151 , let TexCoord x y z = fromMaybe defaultTexCoord ((objTexCoords !-) =<< faceTexCoordIndex) in V3 x y z
145 ) 152 )
146 (position,normal,texcoord) = V.unzip3 . V.concat . map (V.fromList . map toVertex . triangulate . elValue) $ l 153 (position,normal,texcoord) = V.unzip3 . V.concat . map (V.fromList . map toVertex . triangulate . elValue) $ l
147