summaryrefslogtreecommitdiff
path: root/examples/HelloOBJ.hs
diff options
context:
space:
mode:
Diffstat (limited to 'examples/HelloOBJ.hs')
-rw-r--r--examples/HelloOBJ.hs154
1 files changed, 154 insertions, 0 deletions
diff --git a/examples/HelloOBJ.hs b/examples/HelloOBJ.hs
new file mode 100644
index 0000000..10bf248
--- /dev/null
+++ b/examples/HelloOBJ.hs
@@ -0,0 +1,154 @@
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 _ = []
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 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 $ maybe whiteTex (fromMaybe checkerTex . flip Map.lookup textureLib) . mtl_map_Kd <$> mtlLib
80
81addOBJToObjectArray :: GLStorage -> String -> [(GPUMesh, Maybe Text)] -> Map Text TextureData -> IO [LambdaCubeGL.Object]
82addOBJToObjectArray storage slotName objMesh mtlLib = forM objMesh $ \(mesh,mat) -> do
83 obj <- LambdaCubeGL.addMeshToObjectArray storage slotName ["diffuseTexture"] mesh -- diffuseTexture value can change on each model
84 case mat >>= flip Map.lookup mtlLib of
85 Nothing -> return ()
86 Just t -> LambdaCubeGL.updateObjectUniforms obj $ do
87 "diffuseTexture" @= return t -- set model's diffuse texture
88 return obj
89
90main :: IO ()
91main = do
92 Just pipelineDesc <- decodeStrict <$> SB.readFile "hello_obj.json"
93
94 win <- initWindow "LambdaCube 3D DSL OBJ viewer" 640 640
95
96 -- setup render data
97 let inputSchema = makeSchema $ do
98 defObjectArray "objects" Triangles $ do
99 "position" @: Attribute_V4F
100 "normal" @: Attribute_V3F
101 "uvw" @: Attribute_V3F
102 defUniforms $ do
103 "time" @: Float
104 "diffuseTexture" @: FTexture2D
105
106 storage <- LambdaCubeGL.allocStorage inputSchema
107
108 objName <- head . (++ ["cube.obj"]) <$> getArgs
109 -- load OBJ geometry and material descriptions
110 Right (objMesh,mtlLib) <- loadOBJToGPU objName
111 -- load materials textures
112 gpuMtlLib <- uploadMtlLib mtlLib
113 -- add OBJ to pipeline input
114 addOBJToObjectArray storage "objects" objMesh gpuMtlLib
115
116 -- allocate GL pipeline
117 renderer <- LambdaCubeGL.allocRenderer pipelineDesc
118 LambdaCubeGL.setStorage renderer storage >>= \case -- check schema compatibility
119 Just err -> putStrLn err
120 Nothing -> loop
121 where loop = do
122 -- update graphics input
123 GLFW.getWindowSize win >>= \(w,h) -> LambdaCubeGL.setScreenSize storage (fromIntegral w) (fromIntegral h)
124 LambdaCubeGL.updateUniforms storage $ do
125 "time" @= do
126 Just t <- GLFW.getTime
127 return (realToFrac t :: Float)
128 -- render
129 LambdaCubeGL.renderFrame renderer
130 GLFW.swapBuffers win
131 GLFW.pollEvents
132
133 let keyIsPressed k = fmap (==KeyState'Pressed) $ GLFW.getKey win k
134 escape <- keyIsPressed Key'Escape
135 if escape then return () else loop
136
137 LambdaCubeGL.disposeRenderer renderer
138 LambdaCubeGL.disposeStorage storage
139 GLFW.destroyWindow win
140 GLFW.terminate
141
142initWindow :: String -> Int -> Int -> IO Window
143initWindow title width height = do
144 GLFW.init
145 GLFW.defaultWindowHints
146 mapM_ GLFW.windowHint
147 [ WindowHint'ContextVersionMajor 3
148 , WindowHint'ContextVersionMinor 3
149 , WindowHint'OpenGLProfile OpenGLProfile'Core
150 , WindowHint'OpenGLForwardCompat True
151 ]
152 Just win <- GLFW.createWindow width height title Nothing Nothing
153 GLFW.makeContextCurrent $ Just win
154 return win