summaryrefslogtreecommitdiff
path: root/HelloOBJ.hs
diff options
context:
space:
mode:
authorJoe Crayne <joe@jerkface.net>2019-04-09 17:29:40 -0400
committerJoe Crayne <joe@jerkface.net>2019-04-09 17:32:41 -0400
commit21ea6a154e3765b16f6ba6b48773d83e18933881 (patch)
tree298261b8f61235268e21ccf7e0cf3b3f261251d4 /HelloOBJ.hs
parent776f107087941b071bb2227fabdbb45f6c625d32 (diff)
Added HelloOBJ example.
Diffstat (limited to 'HelloOBJ.hs')
-rw-r--r--HelloOBJ.hs156
1 files changed, 156 insertions, 0 deletions
diff --git a/HelloOBJ.hs b/HelloOBJ.hs
new file mode 100644
index 0000000..7ab6b20
--- /dev/null
+++ b/HelloOBJ.hs
@@ -0,0 +1,156 @@
1{-# LANGUAGE PackageImports, LambdaCase, OverloadedStrings, RecordWildCards #-}
2import System.Environment
3import "GLFW-b" Graphics.UI.GLFW as GLFW
4import Data.Text (unpack,Text)
5import Data.List (groupBy,nub)
6import Data.Maybe
7import Control.Monad
8import Data.Map (Map)
9import qualified Data.Map as Map
10import qualified Data.Vector as V
11import qualified Data.ByteString as SB
12
13import LambdaCube.GL as LambdaCubeGL -- renderer
14import LambdaCube.GL.Mesh as LambdaCubeGL
15
16import Codec.Picture as Juicy
17import Data.Aeson
18import Codec.Wavefront
19
20import MtlParser
21
22----------------------------------------------------
23-- See: http://lambdacube3d.com/getting-started
24----------------------------------------------------
25
26objToMesh :: WavefrontOBJ -> [(Mesh,Maybe Text)]
27objToMesh WavefrontOBJ{..} = [(toMesh faceGroup, elMtl . head $ faceGroup) | faceGroup <- faces] where
28 faces = groupBy (\a b -> elMtl a == elMtl b) (V.toList objFaces)
29 toMesh l = Mesh
30 { mAttributes = Map.fromList
31 [ ("position", A_V4F position)
32 , ("normal", A_V3F normal)
33 , ("uvw", A_V3F texcoord)
34 ]
35 , mPrimitive = P_Triangles
36 } where
37 triangulate (Triangle a b c) = [a,b,c]
38 triangulate (Quad a b c d) = [a,b,c, c,d,a]
39 triangulate (Face a b c l) = a : b : c : concatMap (\(x,y) -> [a,x,y]) (zip (c:l) l) -- should work for convex polygons without holes
40 defaultPosition = Location 0 0 0 0
41 defaultNormal = Normal 0 0 0
42 defaultTexCoord = TexCoord 0 0 0
43 v !- i = v V.!? (i-1)
44 toVertex FaceIndex{..} = ( let Location x y z w = fromMaybe defaultPosition (objLocations !- faceLocIndex) in V4 x y z w
45 , let Normal x y z = fromMaybe defaultNormal ((objNormals !-) =<< faceNorIndex) in V3 x y z
46 , let TexCoord x y z = fromMaybe defaultTexCoord ((objTexCoords !-) =<< faceTexCoordIndex) in V3 x y z
47 )
48 (position,normal,texcoord) = V.unzip3 . V.concat . map (V.fromList . map toVertex . triangulate . elValue) $ l
49
50
51loadOBJ :: String -> IO (Either String ([(Mesh,Maybe Text)],MtlLib))
52loadOBJ fname = fromFile fname >>= \case -- load geometry
53 Left err -> putStrLn err >> return (Left err)
54 Right obj@WavefrontOBJ{..} -> do
55 -- load materials
56 mtlLib <- mconcat . V.toList <$> mapM (readMtl . unpack) objMtlLibs
57 return $ Right (objToMesh obj,mtlLib)
58
59loadOBJToGPU :: String -> IO (Either String ([(GPUMesh, Maybe Text)], MtlLib))
60loadOBJToGPU fname = loadOBJ fname >>= \case
61 Left err -> return $ Left err
62 Right (subModels,mtlLib) -> do
63 gpuSubModels <- forM subModels $ \(mesh,mat) -> LambdaCubeGL.uploadMeshToGPU mesh >>= \a -> return (a,mat)
64 return $ Right (gpuSubModels,mtlLib)
65
66uploadMtlLib :: MtlLib -> IO (Map Text (ObjMaterial,TextureData))
67uploadMtlLib mtlLib = do
68 -- collect used textures
69 let usedTextures = nub . concatMap (maybeToList . mtl_map_Kd) $ Map.elems mtlLib
70 whiteImage = Juicy.ImageRGB8 $ Juicy.generateImage (\_ _ -> Juicy.PixelRGB8 255 255 255) 1 1
71 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
72 checkerTex <- LambdaCubeGL.uploadTexture2DToGPU checkerImage
73 -- load images and upload to gpu
74 textureLib <- forM (Map.fromList $ zip usedTextures usedTextures) $ \fname -> Juicy.readImage fname >>= \case
75 Left err -> putStrLn err >> return checkerTex
76 Right img -> LambdaCubeGL.uploadTexture2DToGPU img
77 whiteTex <- LambdaCubeGL.uploadTexture2DToGPU whiteImage
78 -- pair textures and materials
79 return $ (\a -> (a, maybe whiteTex (fromMaybe checkerTex . flip Map.lookup textureLib) . mtl_map_Kd $ a)) <$> mtlLib
80
81addOBJToObjectArray :: GLStorage -> String -> [(GPUMesh, Maybe Text)] -> Map Text (ObjMaterial,TextureData) -> IO [LambdaCubeGL.Object]
82addOBJToObjectArray storage slotName objMesh mtlLib = forM objMesh $ \(mesh,mat) -> do
83 obj <- LambdaCubeGL.addMeshToObjectArray storage slotName ["diffuseTexture","diffuseColor"] mesh -- diffuseTexture and diffuseColor values can change on each model
84 case mat >>= flip Map.lookup mtlLib of
85 Nothing -> return ()
86 Just (ObjMaterial{..},t) -> LambdaCubeGL.updateObjectUniforms obj $ do
87 "diffuseTexture" @= return t -- set model's diffuse texture
88 "diffuseColor" @= let (r,g,b) = mtl_Kd in return (V4 r g b mtl_Tr)
89 return obj
90
91main :: IO ()
92main = do
93 Just pipelineDesc <- decodeStrict <$> SB.readFile "hello_obj.json"
94
95 win <- initWindow "LambdaCube 3D DSL OBJ viewer" 640 640
96
97 -- setup render data
98 let inputSchema = makeSchema $ do
99 defObjectArray "objects" Triangles $ do
100 "position" @: Attribute_V4F
101 "normal" @: Attribute_V3F
102 "uvw" @: Attribute_V3F
103 defUniforms $ do
104 "time" @: Float
105 "diffuseTexture" @: FTexture2D
106 "diffuseColor" @: V4F
107
108 storage <- LambdaCubeGL.allocStorage inputSchema
109
110 objName <- head . (++ ["cube.obj"]) <$> getArgs
111 -- load OBJ geometry and material descriptions
112 Right (objMesh,mtlLib) <- loadOBJToGPU objName
113 -- load materials textures
114 gpuMtlLib <- uploadMtlLib mtlLib
115 -- add OBJ to pipeline input
116 addOBJToObjectArray storage "objects" objMesh gpuMtlLib
117
118 -- allocate GL pipeline
119 renderer <- LambdaCubeGL.allocRenderer pipelineDesc
120 LambdaCubeGL.setStorage renderer storage >>= \case -- check schema compatibility
121 Just err -> putStrLn err
122 Nothing -> loop
123 where loop = do
124 -- update graphics input
125 GLFW.getWindowSize win >>= \(w,h) -> LambdaCubeGL.setScreenSize storage (fromIntegral w) (fromIntegral h)
126 LambdaCubeGL.updateUniforms storage $ do
127 "time" @= do
128 Just t <- GLFW.getTime
129 return (realToFrac t :: Float)
130 -- render
131 LambdaCubeGL.renderFrame renderer
132 GLFW.swapBuffers win
133 GLFW.pollEvents
134
135 let keyIsPressed k = fmap (==KeyState'Pressed) $ GLFW.getKey win k
136 escape <- keyIsPressed Key'Escape
137 if escape then return () else loop
138
139 LambdaCubeGL.disposeRenderer renderer
140 LambdaCubeGL.disposeStorage storage
141 GLFW.destroyWindow win
142 GLFW.terminate
143
144initWindow :: String -> Int -> Int -> IO Window
145initWindow title width height = do
146 GLFW.init
147 GLFW.defaultWindowHints
148 mapM_ GLFW.windowHint
149 [ WindowHint'ContextVersionMajor 3
150 , WindowHint'ContextVersionMinor 3
151 , WindowHint'OpenGLProfile OpenGLProfile'Core
152 , WindowHint'OpenGLForwardCompat True
153 ]
154 Just win <- GLFW.createWindow width height title Nothing Nothing
155 GLFW.makeContextCurrent $ Just win
156 return win