File: SmoothOpenGL3.hs

package info (click to toggle)
haskell-glut 2.4.0.0-1
  • links: PTS, VCS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 1,624 kB
  • ctags: 28
  • sloc: haskell: 10,610; ansic: 121; makefile: 2
file content (266 lines) | stat: -rw-r--r-- 8,305 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
{-
   SmoothOpenGL3.hs (adapted from freeglut's smooth_opengl3.c example)
   Copyright (c) Sven Panne 2009 <sven.panne@aedion.de>
   This file is part of HOpenGL and distributed under a BSD-style license
   See the file LICENSE
-}

import Control.Monad
import Data.List
import Foreign.Marshal.Array
import Foreign.Ptr
import Foreign.Storable
import Graphics.Rendering.OpenGL.Raw.Core31
import Graphics.UI.GLUT
import System.Exit
import System.IO

data State = State {
   vertexBufferName :: BufferObject,
   fgProjectionMatrixIndex :: UniformLocation,
   fgColorIndex :: AttribLocation ,
   fgVertexIndex :: AttribLocation,
   projectionMatrix :: GLmatrix GLfloat }

checkError :: String -> IO ()
checkError functionName = get errors >>= mapM_ reportError
   where reportError e = 
            hPutStrLn stderr (showError e ++ " detected in " ++ functionName)
         showError (Error category message) =
            "GL error" ++ show category ++ " (" ++ message ++ ")"

varray :: [GLfloat]
varray = [
   1, 0, 0, -- red
   5, 5,    -- lower left

   0, 1, 0, -- green
   25, 5,   -- lower right

   0, 0, 1, -- blue
   5, 25 ]  -- upper left

numColorComponents :: NumComponents
numColorComponents = 3

numVertexComponents :: NumComponents
numVertexComponents = 2

sizeOfComponent :: Int
sizeOfComponent = sizeOf (head varray)

stride :: Stride
stride = fromIntegral sizeOfComponent * fromIntegral (numColorComponents + numVertexComponents)

sizeOfVarray :: Int
sizeOfVarray = length varray * sizeOfComponent

numElements :: NumArrayIndices
numElements = fromIntegral sizeOfVarray `div` fromIntegral stride

initBuffer :: IO BufferObject
initBuffer = do
   [bufferObject] <- genObjectNames 1
   bindBuffer ArrayBuffer $= Just bufferObject
   withArray varray $ \buffer ->
      bufferData ArrayBuffer $= (fromIntegral sizeOfVarray, buffer, StaticDraw)
   checkError "initBuffer"
   return bufferObject

vertexShaderSource :: String
vertexShaderSource = unlines [
   "#version 140",
   "uniform mat4 fg_ProjectionMatrix;",
   "in vec4 fg_Color;",
   "in vec4 fg_Vertex;",
   "smooth out vec4 fg_SmoothColor;",
   "void main()",
   "{",
   "   fg_SmoothColor = fg_Color;",
   "   gl_Position = fg_ProjectionMatrix * fg_Vertex;",
   "}" ]

fragmentShaderSource :: String
fragmentShaderSource = unlines [
   "#version 140",
   "smooth in vec4 fg_SmoothColor;",
   "out vec4 fg_FragColor;",
   "void main(void)",
   "{",
   "   fg_FragColor = fg_SmoothColor;",
   "}" ]

checked :: (t -> IO ()) -> (t -> GettableStateVar Bool) -> (t -> GettableStateVar String) -> String -> t -> IO ()
checked action getStatus getInfoLog message object = do
   action object
   status <- get (getStatus object)
   unless status $
      hPutStrLn stderr . ((message ++ " log: ") ++) =<< get (getInfoLog object)

compileAndCheck :: Shader s => s -> IO ()
compileAndCheck = checked compileShader compileStatus shaderInfoLog "compile"

compileShaderSource :: Shader s => [String] -> IO s
compileShaderSource source = do
   [shader] <- genObjectNames 1
   shaderSource shader $= source
   compileAndCheck shader
   return shader

linkAndCheck :: Program -> IO ()
linkAndCheck = checked linkProgram linkStatus programInfoLog "link"

createProgram :: [VertexShader] -> [FragmentShader] -> IO Program
createProgram vertexShaders fragmentShaders = do
   [program] <- genObjectNames 1
   attachedShaders program $= (vertexShaders, fragmentShaders)
   linkAndCheck program
   return program

initShader :: IO (UniformLocation, AttribLocation, AttribLocation)
initShader = do
   vertexShader <- compileShaderSource [vertexShaderSource]
   fragmentShader <- compileShaderSource [fragmentShaderSource]
   program <- createProgram [vertexShader] [fragmentShader]
   currentProgram $= Just program

   projectionMatrixIndex <- get (uniformLocation program "fg_ProjectionMatrix")

   colorIndex <- get (attribLocation program "fg_Color")
   vertexAttribArray colorIndex $= Enabled

   vertexIndex <- get (attribLocation program "fg_Vertex")
   vertexAttribArray vertexIndex $= Enabled

   checkError "initShader"
   return (projectionMatrixIndex, colorIndex, vertexIndex)

initRendering :: IO ()
initRendering = do
   clearColor $= Color4 0 0 0 0
   checkError "initRendering"

myInit :: IO State
myInit = do
   bufferObject <- initBuffer
   (projectionMatrixIndex, colorIndex, vertexIndex) <- initShader
   initRendering
   m <- newMatrix ColumnMajor (replicate 16 0)
   return $ State {
      vertexBufferName = bufferObject,
      fgProjectionMatrixIndex = projectionMatrixIndex,
      fgColorIndex = colorIndex,
      fgVertexIndex = vertexIndex,
      projectionMatrix = m }

dumpInfo :: IO ()
dumpInfo = do
   let dump message var = putStrLn . ((message ++ ": ") ++) =<< get var
   dump "Vendor" vendor
   dump "Renderer" renderer
   dump "Version" glVersion
   dump "GLSL" shadingLanguageVersion
   checkError "dumpInfo"

bufferObjectPtr :: Integral a => a -> Ptr b
bufferObjectPtr = plusPtr (nullPtr :: Ptr GLchar) . fromIntegral

vertexArrayDescriptor :: NumComponents -> NumComponents -> VertexArrayDescriptor a
vertexArrayDescriptor count offset =
   VertexArrayDescriptor count Float stride (bufferObjectPtr (fromIntegral sizeOfComponent * offset))

triangle :: State -> IO ()
triangle state = do
   withMatrix (projectionMatrix state) $ \order buffer ->
      uniformMatrix4fv (fgProjectionMatrixIndex state) 1 (order == RowMajor) buffer
   bindBuffer ArrayBuffer $= Just (vertexBufferName state)
   vertexAttribPointer (fgColorIndex state) $=
      (ToFloat, vertexArrayDescriptor numColorComponents 0)
   vertexAttribPointer (fgVertexIndex state) $=
      (ToFloat, vertexArrayDescriptor numVertexComponents numColorComponents)
   drawArrays Triangles 0 numElements
   checkError "triangle"

-- The OpenGL package offers no interface for glUniformMatrix*fv yet
uniformMatrix4fv :: UniformLocation -> GLsizei -> Bool -> Ptr GLfloat -> IO ()
uniformMatrix4fv location count =
   glUniformMatrix4fv (uniformLocationToGLint location) count . marshalGLboolean
   where marshalGLboolean x = fromIntegral $ case x of
            False -> gl_FALSE
            True -> gl_TRUE
         -- MEGA HACK because UniformLocation is abstract
         uniformLocationToGLint = read . head . tail . words . show

display :: State -> DisplayCallback
display state = do
   clear [ ColorBuffer ]
   triangle state
   flush
   checkError "display"

loadOrtho :: (Matrix m, MatrixComponent a, Fractional a) => m a -> a -> a -> a -> a -> a -> a -> IO ()
loadOrtho m l r b t n f =
   fillMatrix m [
      [2 / (r - l),
       0,
       0,
       0],

      [0,
       2 / (t - b),
       0,
       0],

      [0,
       0,
       -2 / (f - n),
       0],

      [-(r + l) / (r - l),
       -(t + b) / (t - b),
       -(f + n) / (f - n),
       1 ]]

fillMatrix :: (Matrix m, MatrixComponent a) => m a -> [[a]] -> IO ()
fillMatrix m xs =
   withMatrix m $ \order buffer ->
      pokeArray buffer . concat . rearrange order $ xs

rearrange :: MatrixOrder -> [[a]] -> [[a]]
rearrange ColumnMajor = id
rearrange RowMajor = transpose

loadOrtho2D :: (Matrix m, MatrixComponent a, Fractional a) => m a -> a -> a -> a -> a -> IO ()
loadOrtho2D m l r b t = loadOrtho m l r b t (-1) 1

reshape :: State -> ReshapeCallback
reshape state size@(Size w h) = do
   viewport $= (Position 0 0, size)
   let wf = fromIntegral w
       hf = fromIntegral h
   if w <= h
      then loadOrtho2D (projectionMatrix state) 0 30 0 (30 * hf / wf)
      else loadOrtho2D (projectionMatrix state) 0 (30 * wf / hf) 0 30
   checkError "reshape"

keyboard :: KeyboardMouseCallback
keyboard (Char '\27') Down _ _ = exitWith ExitSuccess
keyboard _            _    _ _ = return ()

main :: IO ()
main = do
   (progName, args) <- getArgsAndInitialize
   initialDisplayMode $= [ SingleBuffered, RGBMode ]
   -- add command line argument "classic" for a pre-3.x context
   unless (args == ["classic"]) $ do
      initialContextVersion $= (3, 1)
      initialContextFlags $= [ ForwardCompatibleContext, DebugContext ]
   initialWindowSize $= Size 500 500
   initialWindowPosition $= Position 100 100
   createWindow progName
   dumpInfo
   state <- myInit
   displayCallback $= display state
   reshapeCallback $= Just (reshape state)
   keyboardMouseCallback $= Just keyboard
   mainLoop