diff options
Diffstat (limited to 'src/LambdaCube/GL/Type.hs')
-rw-r--r-- | src/LambdaCube/GL/Type.hs | 541 |
1 files changed, 541 insertions, 0 deletions
diff --git a/src/LambdaCube/GL/Type.hs b/src/LambdaCube/GL/Type.hs new file mode 100644 index 0000000..c82a8f0 --- /dev/null +++ b/src/LambdaCube/GL/Type.hs | |||
@@ -0,0 +1,541 @@ | |||
1 | {-# LANGUAGE ExistentialQuantification, FlexibleInstances, GeneralizedNewtypeDeriving, ScopedTypeVariables #-} | ||
2 | module LambdaCube.GL.Type where | ||
3 | |||
4 | import Data.ByteString.Char8 (ByteString) | ||
5 | import Data.IORef | ||
6 | import Data.Int | ||
7 | import Data.IntMap (IntMap) | ||
8 | import Data.Set (Set) | ||
9 | import Data.Trie (Trie) | ||
10 | import Data.Vector (Vector) | ||
11 | import Data.Word | ||
12 | import Foreign.Ptr | ||
13 | import Foreign.Storable | ||
14 | |||
15 | import Graphics.GL.Core33 | ||
16 | |||
17 | import Linear | ||
18 | import IR | ||
19 | |||
20 | --------------- | ||
21 | -- Input API -- | ||
22 | --------------- | ||
23 | {- | ||
24 | -- Buffer | ||
25 | compileBuffer :: [Array] -> IO Buffer | ||
26 | bufferSize :: Buffer -> Int | ||
27 | arraySize :: Buffer -> Int -> Int | ||
28 | arrayType :: Buffer -> Int -> ArrayType | ||
29 | |||
30 | -- Object | ||
31 | addObject :: Renderer -> ByteString -> Primitive -> Maybe (IndexStream Buffer) -> Trie (Stream Buffer) -> [ByteString] -> IO Object | ||
32 | removeObject :: Renderer -> Object -> IO () | ||
33 | objectUniformSetter :: Object -> Trie InputSetter | ||
34 | -} | ||
35 | |||
36 | data Buffer -- internal type | ||
37 | = Buffer | ||
38 | { bufArrays :: Vector ArrayDesc | ||
39 | , bufGLObj :: GLuint | ||
40 | } | ||
41 | deriving (Show,Eq) | ||
42 | |||
43 | data ArrayDesc | ||
44 | = ArrayDesc | ||
45 | { arrType :: ArrayType | ||
46 | , arrLength :: Int -- item count | ||
47 | , arrOffset :: Int -- byte position in buffer | ||
48 | , arrSize :: Int -- size in bytes | ||
49 | } | ||
50 | deriving (Show,Eq) | ||
51 | |||
52 | {- | ||
53 | handles: | ||
54 | uniforms | ||
55 | textures | ||
56 | buffers | ||
57 | objects | ||
58 | |||
59 | GLStorage can be attached to GLRenderer | ||
60 | -} | ||
61 | |||
62 | {- | ||
63 | pipeline input: | ||
64 | - independent from pipeline | ||
65 | - per object features: enable/disable visibility, set render ordering | ||
66 | -} | ||
67 | |||
68 | data SlotSchema | ||
69 | = SlotSchema | ||
70 | { primitive :: FetchPrimitive | ||
71 | , attributes :: Trie StreamType | ||
72 | } | ||
73 | deriving Show | ||
74 | |||
75 | data PipelineSchema | ||
76 | = PipelineSchema | ||
77 | { slots :: Trie SlotSchema | ||
78 | , uniforms :: Trie InputType | ||
79 | } | ||
80 | deriving Show | ||
81 | |||
82 | data GLUniform = forall a. Storable a => GLUniform !InputType !(IORef a) | ||
83 | |||
84 | instance Show GLUniform where | ||
85 | show (GLUniform t _) = "GLUniform " ++ show t | ||
86 | |||
87 | data OrderJob | ||
88 | = Generate | ||
89 | | Reorder | ||
90 | | Ordered | ||
91 | |||
92 | data GLSlot | ||
93 | = GLSlot | ||
94 | { objectMap :: IntMap Object | ||
95 | , sortedObjects :: Vector (Int,Object) | ||
96 | , orderJob :: OrderJob | ||
97 | } | ||
98 | |||
99 | data GLStorage | ||
100 | = GLStorage | ||
101 | { schema :: PipelineSchema | ||
102 | , slotMap :: Trie SlotName | ||
103 | , slotVector :: Vector (IORef GLSlot) | ||
104 | , objSeed :: IORef Int | ||
105 | , uniformSetter :: Trie InputSetter | ||
106 | , uniformSetup :: Trie GLUniform | ||
107 | , screenSize :: IORef (Word,Word) | ||
108 | , pipelines :: IORef (Vector (Maybe GLRenderer)) -- attached pipelines | ||
109 | } | ||
110 | |||
111 | data Object -- internal type | ||
112 | = Object | ||
113 | { objSlot :: SlotName | ||
114 | , objPrimitive :: Primitive | ||
115 | , objIndices :: Maybe (IndexStream Buffer) | ||
116 | , objAttributes :: Trie (Stream Buffer) | ||
117 | , objUniSetter :: Trie InputSetter | ||
118 | , objUniSetup :: Trie GLUniform | ||
119 | , objOrder :: IORef Int | ||
120 | , objEnabled :: IORef Bool | ||
121 | , objId :: Int | ||
122 | , objCommands :: IORef (Vector (Vector [GLObjectCommand])) -- pipeline id, program name, commands | ||
123 | } | ||
124 | |||
125 | -------------- | ||
126 | -- Pipeline -- | ||
127 | -------------- | ||
128 | |||
129 | data GLProgram | ||
130 | = GLProgram | ||
131 | { shaderObjects :: [GLuint] | ||
132 | , programObject :: GLuint | ||
133 | , inputUniforms :: Trie GLint | ||
134 | , inputTextures :: Trie GLint -- all input textures (render texture + uniform texture) | ||
135 | , inputTextureUniforms :: Set ByteString | ||
136 | , inputStreams :: Trie (GLuint,ByteString) | ||
137 | } | ||
138 | |||
139 | data GLTexture | ||
140 | = GLTexture | ||
141 | { glTextureObject :: GLuint | ||
142 | , glTextureTarget :: GLenum | ||
143 | } | ||
144 | |||
145 | data InputConnection | ||
146 | = InputConnection | ||
147 | { icId :: Int -- identifier (vector index) for attached pipeline | ||
148 | , icInput :: GLStorage | ||
149 | , icSlotMapPipelineToInput :: Vector SlotName -- GLRenderer to GLStorage slot name mapping | ||
150 | , icSlotMapInputToPipeline :: Vector (Maybe SlotName) -- GLStorage to GLRenderer slot name mapping | ||
151 | } | ||
152 | |||
153 | data GLStream | ||
154 | = GLStream | ||
155 | { glStreamCommands :: IORef [GLObjectCommand] | ||
156 | , glStreamPrimitive :: Primitive | ||
157 | , glStreamAttributes :: Trie (Stream Buffer) | ||
158 | , glStreamProgram :: ProgramName | ||
159 | } | ||
160 | |||
161 | data GLRenderer | ||
162 | = GLRenderer | ||
163 | { glPrograms :: Vector GLProgram | ||
164 | , glTextures :: Vector GLTexture | ||
165 | , glSamplers :: Vector GLSampler | ||
166 | , glTargets :: Vector GLRenderTarget | ||
167 | , glCommands :: [GLCommand] | ||
168 | , glSlotPrograms :: Vector [ProgramName] -- programs depend on a slot | ||
169 | , glInput :: IORef (Maybe InputConnection) | ||
170 | , glSlotNames :: Vector ByteString | ||
171 | , glVAO :: GLuint | ||
172 | , glTexUnitMapping :: Trie (IORef GLint) -- maps texture uniforms to texture units | ||
173 | , glStreams :: Vector GLStream | ||
174 | } | ||
175 | |||
176 | data GLSampler | ||
177 | = GLSampler | ||
178 | { samplerObject :: GLuint | ||
179 | } | ||
180 | |||
181 | data GLRenderTarget | ||
182 | = GLRenderTarget | ||
183 | { framebufferObject :: GLuint | ||
184 | , framebufferDrawbuffers :: Maybe [GLenum] | ||
185 | } | ||
186 | |||
187 | data GLCommand | ||
188 | = GLSetRasterContext !RasterContext | ||
189 | | GLSetAccumulationContext !AccumulationContext | ||
190 | | GLSetRenderTarget !GLuint !(Maybe [GLenum]) | ||
191 | | GLSetProgram !GLuint | ||
192 | | GLSetSamplerUniform !GLint !GLint (IORef GLint) -- sampler index, texture unit, IORef stores the actual texture unit mapping | ||
193 | | GLSetTexture !GLenum !GLuint !GLuint | ||
194 | | GLSetSampler !GLuint !GLuint | ||
195 | | GLRenderSlot !SlotName !ProgramName | ||
196 | | GLRenderStream !StreamName !ProgramName | ||
197 | | GLClearRenderTarget [ClearImage] | ||
198 | | GLGenerateMipMap !GLenum !GLenum | ||
199 | | GLSaveImage FrameBufferComponent ImageRef -- from framebuffer component to texture (image) | ||
200 | | GLLoadImage ImageRef FrameBufferComponent -- from texture (image) to framebuffer component | ||
201 | deriving Show | ||
202 | |||
203 | instance Show (IORef GLint) where | ||
204 | show _ = "(IORef GLint)" | ||
205 | |||
206 | data GLObjectCommand | ||
207 | = GLSetUniform !GLint !GLUniform | ||
208 | | GLBindTexture !GLenum !(IORef GLint) !GLUniform -- binds the texture from the gluniform to the specified texture unit and target | ||
209 | | GLSetVertexAttribArray !GLuint !GLuint !GLint !GLenum !(Ptr ()) -- index buffer size type pointer | ||
210 | | GLSetVertexAttribIArray !GLuint !GLuint !GLint !GLenum !(Ptr ()) -- index buffer size type pointer | ||
211 | | GLSetVertexAttrib !GLuint !(Stream Buffer) -- index value | ||
212 | | GLDrawArrays !GLenum !GLint !GLsizei -- mode first count | ||
213 | | GLDrawElements !GLenum !GLsizei !GLenum !GLuint !(Ptr ()) -- mode count type buffer indicesPtr | ||
214 | deriving Show | ||
215 | |||
216 | type SetterFun a = a -> IO () | ||
217 | |||
218 | -- user will provide scalar input data via this type | ||
219 | data InputSetter | ||
220 | = SBool (SetterFun Bool) | ||
221 | | SV2B (SetterFun V2B) | ||
222 | | SV3B (SetterFun V3B) | ||
223 | | SV4B (SetterFun V4B) | ||
224 | | SWord (SetterFun Word32) | ||
225 | | SV2U (SetterFun V2U) | ||
226 | | SV3U (SetterFun V3U) | ||
227 | | SV4U (SetterFun V4U) | ||
228 | | SInt (SetterFun Int32) | ||
229 | | SV2I (SetterFun V2I) | ||
230 | | SV3I (SetterFun V3I) | ||
231 | | SV4I (SetterFun V4I) | ||
232 | | SFloat (SetterFun Float) | ||
233 | | SV2F (SetterFun V2F) | ||
234 | | SV3F (SetterFun V3F) | ||
235 | | SV4F (SetterFun V4F) | ||
236 | | SM22F (SetterFun M22F) | ||
237 | | SM23F (SetterFun M23F) | ||
238 | | SM24F (SetterFun M24F) | ||
239 | | SM32F (SetterFun M32F) | ||
240 | | SM33F (SetterFun M33F) | ||
241 | | SM34F (SetterFun M34F) | ||
242 | | SM42F (SetterFun M42F) | ||
243 | | SM43F (SetterFun M43F) | ||
244 | | SM44F (SetterFun M44F) | ||
245 | -- shadow textures | ||
246 | | SSTexture1D | ||
247 | | SSTexture2D | ||
248 | | SSTextureCube | ||
249 | | SSTexture1DArray | ||
250 | | SSTexture2DArray | ||
251 | | SSTexture2DRect | ||
252 | -- float textures | ||
253 | | SFTexture1D | ||
254 | | SFTexture2D (SetterFun TextureData) | ||
255 | | SFTexture3D | ||
256 | | SFTextureCube | ||
257 | | SFTexture1DArray | ||
258 | | SFTexture2DArray | ||
259 | | SFTexture2DMS | ||
260 | | SFTexture2DMSArray | ||
261 | | SFTextureBuffer | ||
262 | | SFTexture2DRect | ||
263 | -- int textures | ||
264 | | SITexture1D | ||
265 | | SITexture2D | ||
266 | | SITexture3D | ||
267 | | SITextureCube | ||
268 | | SITexture1DArray | ||
269 | | SITexture2DArray | ||
270 | | SITexture2DMS | ||
271 | | SITexture2DMSArray | ||
272 | | SITextureBuffer | ||
273 | | SITexture2DRect | ||
274 | -- uint textures | ||
275 | | SUTexture1D | ||
276 | | SUTexture2D | ||
277 | | SUTexture3D | ||
278 | | SUTextureCube | ||
279 | | SUTexture1DArray | ||
280 | | SUTexture2DArray | ||
281 | | SUTexture2DMS | ||
282 | | SUTexture2DMSArray | ||
283 | | SUTextureBuffer | ||
284 | | SUTexture2DRect | ||
285 | |||
286 | -- buffer handling | ||
287 | {- | ||
288 | user can fills a buffer (continuous memory region) | ||
289 | each buffer have a data descriptor, what describes the | ||
290 | buffer content. e.g. a buffer can contain more arrays of stream types | ||
291 | -} | ||
292 | |||
293 | -- user will provide stream data using this setup function | ||
294 | type BufferSetter = (Ptr () -> IO ()) -> IO () | ||
295 | |||
296 | -- specifies array component type (stream type in storage side) | ||
297 | -- this type can be overridden in GPU side, e.g ArrWord8 can be seen as TFloat or TWord also | ||
298 | data ArrayType | ||
299 | = ArrWord8 | ||
300 | | ArrWord16 | ||
301 | | ArrWord32 | ||
302 | | ArrInt8 | ||
303 | | ArrInt16 | ||
304 | | ArrInt32 | ||
305 | | ArrFloat | ||
306 | | ArrHalf -- Hint: half float is not supported in haskell | ||
307 | deriving (Show,Eq,Ord) | ||
308 | |||
309 | sizeOfArrayType :: ArrayType -> Int | ||
310 | sizeOfArrayType ArrWord8 = 1 | ||
311 | sizeOfArrayType ArrWord16 = 2 | ||
312 | sizeOfArrayType ArrWord32 = 4 | ||
313 | sizeOfArrayType ArrInt8 = 1 | ||
314 | sizeOfArrayType ArrInt16 = 2 | ||
315 | sizeOfArrayType ArrInt32 = 4 | ||
316 | sizeOfArrayType ArrFloat = 4 | ||
317 | sizeOfArrayType ArrHalf = 2 | ||
318 | |||
319 | -- describes an array in a buffer | ||
320 | data Array -- array type, element count (NOT byte size!), setter | ||
321 | = Array ArrayType Int BufferSetter | ||
322 | |||
323 | -- dev hint: this should be InputType | ||
324 | -- we restrict StreamType using type class | ||
325 | -- subset of InputType, describes a stream type (in GPU side) | ||
326 | data StreamType | ||
327 | = Attribute_Word | ||
328 | | Attribute_V2U | ||
329 | | Attribute_V3U | ||
330 | | Attribute_V4U | ||
331 | | Attribute_Int | ||
332 | | Attribute_V2I | ||
333 | | Attribute_V3I | ||
334 | | Attribute_V4I | ||
335 | | Attribute_Float | ||
336 | | Attribute_V2F | ||
337 | | Attribute_V3F | ||
338 | | Attribute_V4F | ||
339 | | Attribute_M22F | ||
340 | | Attribute_M23F | ||
341 | | Attribute_M24F | ||
342 | | Attribute_M32F | ||
343 | | Attribute_M33F | ||
344 | | Attribute_M34F | ||
345 | | Attribute_M42F | ||
346 | | Attribute_M43F | ||
347 | | Attribute_M44F | ||
348 | deriving (Show,Eq,Ord) | ||
349 | |||
350 | toStreamType :: InputType -> Maybe StreamType | ||
351 | toStreamType Word = Just Attribute_Word | ||
352 | toStreamType V2U = Just Attribute_V2U | ||
353 | toStreamType V3U = Just Attribute_V3U | ||
354 | toStreamType V4U = Just Attribute_V4U | ||
355 | toStreamType Int = Just Attribute_Int | ||
356 | toStreamType V2I = Just Attribute_V2I | ||
357 | toStreamType V3I = Just Attribute_V3I | ||
358 | toStreamType V4I = Just Attribute_V4I | ||
359 | toStreamType Float = Just Attribute_Float | ||
360 | toStreamType V2F = Just Attribute_V2F | ||
361 | toStreamType V3F = Just Attribute_V3F | ||
362 | toStreamType V4F = Just Attribute_V4F | ||
363 | toStreamType M22F = Just Attribute_M22F | ||
364 | toStreamType M23F = Just Attribute_M23F | ||
365 | toStreamType M24F = Just Attribute_M24F | ||
366 | toStreamType M32F = Just Attribute_M32F | ||
367 | toStreamType M33F = Just Attribute_M33F | ||
368 | toStreamType M34F = Just Attribute_M34F | ||
369 | toStreamType M42F = Just Attribute_M42F | ||
370 | toStreamType M43F = Just Attribute_M43F | ||
371 | toStreamType M44F = Just Attribute_M44F | ||
372 | toStreamType _ = Nothing | ||
373 | |||
374 | fromStreamType :: StreamType -> InputType | ||
375 | fromStreamType Attribute_Word = Word | ||
376 | fromStreamType Attribute_V2U = V2U | ||
377 | fromStreamType Attribute_V3U = V3U | ||
378 | fromStreamType Attribute_V4U = V4U | ||
379 | fromStreamType Attribute_Int = Int | ||
380 | fromStreamType Attribute_V2I = V2I | ||
381 | fromStreamType Attribute_V3I = V3I | ||
382 | fromStreamType Attribute_V4I = V4I | ||
383 | fromStreamType Attribute_Float = Float | ||
384 | fromStreamType Attribute_V2F = V2F | ||
385 | fromStreamType Attribute_V3F = V3F | ||
386 | fromStreamType Attribute_V4F = V4F | ||
387 | fromStreamType Attribute_M22F = M22F | ||
388 | fromStreamType Attribute_M23F = M23F | ||
389 | fromStreamType Attribute_M24F = M24F | ||
390 | fromStreamType Attribute_M32F = M32F | ||
391 | fromStreamType Attribute_M33F = M33F | ||
392 | fromStreamType Attribute_M34F = M34F | ||
393 | fromStreamType Attribute_M42F = M42F | ||
394 | fromStreamType Attribute_M43F = M43F | ||
395 | fromStreamType Attribute_M44F = M44F | ||
396 | |||
397 | -- user can specify streams using Stream type | ||
398 | -- a stream can be constant (ConstXXX) or can came from a buffer | ||
399 | data Stream b | ||
400 | = ConstWord Word32 | ||
401 | | ConstV2U V2U | ||
402 | | ConstV3U V3U | ||
403 | | ConstV4U V4U | ||
404 | | ConstInt Int32 | ||
405 | | ConstV2I V2I | ||
406 | | ConstV3I V3I | ||
407 | | ConstV4I V4I | ||
408 | | ConstFloat Float | ||
409 | | ConstV2F V2F | ||
410 | | ConstV3F V3F | ||
411 | | ConstV4F V4F | ||
412 | | ConstM22F M22F | ||
413 | | ConstM23F M23F | ||
414 | | ConstM24F M24F | ||
415 | | ConstM32F M32F | ||
416 | | ConstM33F M33F | ||
417 | | ConstM34F M34F | ||
418 | | ConstM42F M42F | ||
419 | | ConstM43F M43F | ||
420 | | ConstM44F M44F | ||
421 | | Stream | ||
422 | { streamType :: StreamType | ||
423 | , streamBuffer :: b | ||
424 | , streamArrIdx :: Int | ||
425 | , streamStart :: Int | ||
426 | , streamLength :: Int | ||
427 | } | ||
428 | deriving Show | ||
429 | |||
430 | streamToStreamType :: Stream a -> StreamType | ||
431 | streamToStreamType s = case s of | ||
432 | ConstWord _ -> Attribute_Word | ||
433 | ConstV2U _ -> Attribute_V2U | ||
434 | ConstV3U _ -> Attribute_V3U | ||
435 | ConstV4U _ -> Attribute_V4U | ||
436 | ConstInt _ -> Attribute_Int | ||
437 | ConstV2I _ -> Attribute_V2I | ||
438 | ConstV3I _ -> Attribute_V3I | ||
439 | ConstV4I _ -> Attribute_V4I | ||
440 | ConstFloat _ -> Attribute_Float | ||
441 | ConstV2F _ -> Attribute_V2F | ||
442 | ConstV3F _ -> Attribute_V3F | ||
443 | ConstV4F _ -> Attribute_V4F | ||
444 | ConstM22F _ -> Attribute_M22F | ||
445 | ConstM23F _ -> Attribute_M23F | ||
446 | ConstM24F _ -> Attribute_M24F | ||
447 | ConstM32F _ -> Attribute_M32F | ||
448 | ConstM33F _ -> Attribute_M33F | ||
449 | ConstM34F _ -> Attribute_M34F | ||
450 | ConstM42F _ -> Attribute_M42F | ||
451 | ConstM43F _ -> Attribute_M43F | ||
452 | ConstM44F _ -> Attribute_M44F | ||
453 | Stream t _ _ _ _ -> t | ||
454 | |||
455 | -- stream of index values (for index buffer) | ||
456 | data IndexStream b | ||
457 | = IndexStream | ||
458 | { indexBuffer :: b | ||
459 | , indexArrIdx :: Int | ||
460 | , indexStart :: Int | ||
461 | , indexLength :: Int | ||
462 | } | ||
463 | |||
464 | newtype TextureData | ||
465 | = TextureData | ||
466 | { textureObject :: GLuint | ||
467 | } | ||
468 | deriving Storable | ||
469 | |||
470 | data Primitive | ||
471 | = TriangleStrip | ||
472 | | TriangleList | ||
473 | | TriangleFan | ||
474 | | LineStrip | ||
475 | | LineList | ||
476 | | PointList | ||
477 | | TriangleStripAdjacency | ||
478 | | TriangleListAdjacency | ||
479 | | LineStripAdjacency | ||
480 | | LineListAdjacency | ||
481 | deriving (Eq,Ord,Bounded,Enum,Show) | ||
482 | |||
483 | type StreamSetter = Stream Buffer -> IO () | ||
484 | |||
485 | -- storable instances | ||
486 | instance Storable a => Storable (V2 a) where | ||
487 | sizeOf _ = 2 * sizeOf (undefined :: a) | ||
488 | alignment _ = sizeOf (undefined :: a) | ||
489 | |||
490 | peek q = do | ||
491 | let p = castPtr q :: Ptr a | ||
492 | k = sizeOf (undefined :: a) | ||
493 | x <- peek p | ||
494 | y <- peekByteOff p k | ||
495 | return $! (V2 x y) | ||
496 | |||
497 | poke q (V2 x y) = do | ||
498 | let p = castPtr q :: Ptr a | ||
499 | k = sizeOf (undefined :: a) | ||
500 | poke p x | ||
501 | pokeByteOff p k y | ||
502 | |||
503 | instance Storable a => Storable (V3 a) where | ||
504 | sizeOf _ = 3 * sizeOf (undefined :: a) | ||
505 | alignment _ = sizeOf (undefined :: a) | ||
506 | |||
507 | peek q = do | ||
508 | let p = castPtr q :: Ptr a | ||
509 | k = sizeOf (undefined :: a) | ||
510 | x <- peek p | ||
511 | y <- peekByteOff p k | ||
512 | z <- peekByteOff p (k*2) | ||
513 | return $! (V3 x y z) | ||
514 | |||
515 | poke q (V3 x y z) = do | ||
516 | let p = castPtr q :: Ptr a | ||
517 | k = sizeOf (undefined :: a) | ||
518 | poke p x | ||
519 | pokeByteOff p k y | ||
520 | pokeByteOff p (k*2) z | ||
521 | |||
522 | instance Storable a => Storable (V4 a) where | ||
523 | sizeOf _ = 4 * sizeOf (undefined :: a) | ||
524 | alignment _ = sizeOf (undefined :: a) | ||
525 | |||
526 | peek q = do | ||
527 | let p = castPtr q :: Ptr a | ||
528 | k = sizeOf (undefined :: a) | ||
529 | x <- peek p | ||
530 | y <- peekByteOff p k | ||
531 | z <- peekByteOff p (k*2) | ||
532 | w <- peekByteOff p (k*3) | ||
533 | return $! (V4 x y z w) | ||
534 | |||
535 | poke q (V4 x y z w) = do | ||
536 | let p = castPtr q :: Ptr a | ||
537 | k = sizeOf (undefined :: a) | ||
538 | poke p x | ||
539 | pokeByteOff p k y | ||
540 | pokeByteOff p (k*2) z | ||
541 | pokeByteOff p (k*3) w | ||