summaryrefslogtreecommitdiff
path: root/examples/pickInt.hs
diff options
context:
space:
mode:
Diffstat (limited to 'examples/pickInt.hs')
-rw-r--r--examples/pickInt.hs184
1 files changed, 184 insertions, 0 deletions
diff --git a/examples/pickInt.hs b/examples/pickInt.hs
new file mode 100644
index 0000000..2443c8b
--- /dev/null
+++ b/examples/pickInt.hs
@@ -0,0 +1,184 @@
1{-# LANGUAGE PackageImports, LambdaCase, OverloadedStrings, StandaloneDeriving, ViewPatterns #-}
2import Control.Monad
3import Data.Aeson
4import Data.Vect (Mat4(..), Vec3(..), Vec4(..))
5import Graphics.GL.Core33 as GL
6import LambdaCube.GL as LambdaCubeGL
7import LambdaCube.GL.Mesh as LambdaCubeGL
8import Text.Printf
9import "GLFW-b" Graphics.UI.GLFW as GLFW
10import qualified Data.ByteString as SB
11import qualified Data.Map as Map
12import qualified Data.Vect as Vc
13import qualified Data.Vector as V
14import qualified Foreign as F
15import qualified Foreign.C.Types as F
16import qualified LambdaCube.GL.Type as LC
17import qualified LambdaCube.Linear as LCLin
18
19----------------------------------------------------
20-- See: http://lambdacube3d.com/getting-started
21----------------------------------------------------
22
23screenDim :: (,) Int Int
24screenDim = (,) 800 600
25(,) screenW screenH = screenDim
26
27main :: IO ()
28main = do
29 Just pipePickDesc <- decodeStrict <$> SB.readFile "pickInt.json"
30 Just pipeDrawDesc <- decodeStrict <$> SB.readFile "pickIntDraw.json"
31
32 win <- initWindow "LambdaCube 3D integer picking" 800 600
33
34 -- setup render data
35 let inputSchema = makeSchema $ do
36 defObjectArray "objects" Triangles $ do
37 "position" @: Attribute_V2F
38 "id" @: Attribute_Int
39 "color" @: Attribute_V4F
40 defUniforms $ do
41 "viewProj" @: M44F
42
43 storage <- LambdaCubeGL.allocStorage inputSchema
44
45 -- upload geometry to GPU and add to pipeline input
46 LambdaCubeGL.uploadMeshToGPU triangleA >>= LambdaCubeGL.addMeshToObjectArray storage "objects" []
47 LambdaCubeGL.uploadMeshToGPU triangleB >>= LambdaCubeGL.addMeshToObjectArray storage "objects" []
48
49 -- allocate GL pipeline
50 pipePick <- LambdaCubeGL.allocRenderer pipePickDesc
51 pipeDraw <- LambdaCubeGL.allocRenderer pipeDrawDesc
52 errPick <- LambdaCubeGL.setStorage pipePick storage
53 errDraw <- LambdaCubeGL.setStorage pipeDraw storage
54 case (errPick, errDraw) of -- check schema compatibility
55 (Just err, _) -> putStrLn err
56 (_, Just err) -> putStrLn err
57 (Nothing, Nothing) -> loop
58 where loop = do
59 -- update graphics input
60 GLFW.getWindowSize win >>= \(w,h) -> LambdaCubeGL.setScreenSize storage (fromIntegral w) (fromIntegral h)
61 LambdaCubeGL.updateUniforms storage $ do
62 let (,) x y = (,) 0 0
63 cvpos = Vec3 x (-y) 0
64 toScreen = screenM screenW screenH
65 "viewProj" @= pure (mat4ToM44F $! (Vc.fromProjective $! Vc.translation cvpos) Vc..*. toScreen)
66
67 let pickPoints =
68 [ (0, 0) -- should be black
69 , (200, 200) -- ..blue, ffff0000
70 , (600, 400) -- ..red, ff0000ff
71 ] :: [(,) Int Int]
72
73 -- render to render texture
74 LambdaCubeGL.renderFrame pipePick
75 case LC.glOutputs pipePick of
76 [LC.GLOutputRenderTexture (fromIntegral -> fbo) _rendTex] -> do
77 rtexPicks <- collectPicks fbo pickPoints
78 printPicks pickPoints rtexPicks
79 x -> error $ "Unexpected outputs: " <> show x
80
81 -- render to framebuffer & pick
82 LambdaCubeGL.renderFrame pipeDraw
83 colorPicks <- collectPicks 0 pickPoints
84 printPicks pickPoints colorPicks
85
86 GLFW.swapBuffers win
87 GLFW.pollEvents
88
89 let keyIsPressed k = fmap (==KeyState'Pressed) $ GLFW.getKey win k
90 escape <- keyIsPressed Key'Escape
91 if escape then return () else loop
92 collectPicks :: Int -> [(,) Int Int] -> IO [Int]
93 collectPicks fb picks =
94 forM picks $ (fromIntegral <$>) . pickFrameBuffer fb screenDim
95 printPicks pickPoints colorPicks = do
96 forM_ (zip pickPoints colorPicks) $ \((x,y), col)-> do
97 printf "%d:%d: %x " x y col
98 putStrLn ""
99
100 LambdaCubeGL.disposeRenderer pipePick
101 LambdaCubeGL.disposeRenderer pipeDraw
102 LambdaCubeGL.disposeStorage storage
103 GLFW.destroyWindow win
104 GLFW.terminate
105
106deriving instance Show (LC.GLOutput)
107deriving instance Show (LC.GLTexture)
108
109-- geometry data: triangles
110scale = 250.0
111s = scale
112
113triangleA :: LambdaCubeGL.Mesh
114triangleA = Mesh
115 { mAttributes = Map.fromList
116 [ ("position", A_V2F $ V.fromList [V2 s s, V2 s (-s), V2 (-s) (-s)])
117 , ("color", A_V4F $ V.fromList $ take 4 $ repeat $ V4 1 0 0 1)
118 , ("id", A_Int $ V.fromList [1, 1, 1])
119 ]
120 , mPrimitive = P_Triangles
121 }
122
123triangleB :: LambdaCubeGL.Mesh
124triangleB = Mesh
125 { mAttributes = Map.fromList
126 [ ("position", A_V2F $ V.fromList [V2 s s, V2 (-s) (-s), V2 (-s) s])
127 , ("color", A_V4F $ V.fromList $ take 4 $ repeat $ V4 0 0 1 1)
128 , ("id", A_Int $ V.fromList [2, 2, 2])
129 ]
130 , mPrimitive = P_Triangles
131 }
132
133vec4ToV4F :: Vec4 -> LCLin.V4F
134vec4ToV4F (Vc.Vec4 x y z w) = LCLin.V4 x y z w
135
136mat4ToM44F :: Mat4 -> LCLin.M44F
137mat4ToM44F (Mat4 a b c d) = LCLin.V4 (vec4ToV4F a) (vec4ToV4F b) (vec4ToV4F c) (vec4ToV4F d)
138
139screenM :: Int -> Int -> Mat4
140screenM w h = scaleM
141 where (fw, fh) = (fromIntegral w, fromIntegral h)
142 scaleM = Vc.Mat4 (Vc.Vec4 (1/fw) 0 0 0)
143 (Vc.Vec4 0 (1/fh) 0 0)
144 (Vc.Vec4 0 0 1 0)
145 (Vc.Vec4 0 0 0 0.5)
146
147pickFrameBuffer
148 :: Int -- ^ framebuffer
149 -> (,) Int Int -- ^ FB dimensions
150 -> (,) Int Int -- ^ pick coordinates
151 -> IO F.Word32 -- ^ resultant pixel value
152pickFrameBuffer fb (w, h) (x, y) = do
153 glFinish
154 glBindFramebuffer GL_READ_FRAMEBUFFER $ fromIntegral fb
155 glReadBuffer GL_BACK_LEFT
156 withFrameBuffer x (h - y - 1) 1 1 $ \p -> fromIntegral <$> F.peek (F.castPtr p :: F.Ptr F.Word32)
157
158withFrameBuffer :: Int -> Int -> Int -> Int -> (F.Ptr F.Word8 -> IO a) -> IO a
159withFrameBuffer x y w h fn = F.allocaBytes (w*h*4) $ \p -> do
160 glPixelStorei GL_UNPACK_LSB_FIRST 0
161 glPixelStorei GL_UNPACK_SWAP_BYTES 0
162 glPixelStorei GL_UNPACK_ROW_LENGTH $ fromIntegral w
163 glPixelStorei GL_UNPACK_IMAGE_HEIGHT 0
164 glPixelStorei GL_UNPACK_SKIP_ROWS 0
165 glPixelStorei GL_UNPACK_SKIP_PIXELS 0
166 glPixelStorei GL_UNPACK_SKIP_IMAGES 0
167 glPixelStorei GL_UNPACK_ALIGNMENT 1
168 glReadPixels (fromIntegral x) (fromIntegral y) (fromIntegral w) (fromIntegral h) GL_RGBA GL_UNSIGNED_BYTE $ F.castPtr p
169 glPixelStorei GL_UNPACK_ROW_LENGTH 0
170 fn p
171
172initWindow :: String -> Int -> Int -> IO Window
173initWindow title width height = do
174 GLFW.init
175 GLFW.defaultWindowHints
176 mapM_ GLFW.windowHint
177 [ WindowHint'ContextVersionMajor 3
178 , WindowHint'ContextVersionMinor 3
179 , WindowHint'OpenGLProfile OpenGLProfile'Core
180 , WindowHint'OpenGLForwardCompat True
181 ]
182 Just win <- GLFW.createWindow width height title Nothing Nothing
183 GLFW.makeContextCurrent $ Just win
184 return win