summaryrefslogtreecommitdiff
path: root/ddl/out/LambdaCube.IR.purs
diff options
context:
space:
mode:
authorCsaba Hruska <csaba.hruska@gmail.com>2016-01-29 15:27:53 +0100
committerCsaba Hruska <csaba.hruska@gmail.com>2016-01-29 15:27:53 +0100
commitfe9a7c6d0af59227ff34b098f2a5ba1359790ae8 (patch)
tree3bb7170620c4b914d8bc39127af1e4fb4627fab3 /ddl/out/LambdaCube.IR.purs
parent0c885c5c6bfb69c543635fd08d697ce44f24642d (diff)
add Schema to IR module, also use namespace
Diffstat (limited to 'ddl/out/LambdaCube.IR.purs')
-rw-r--r--ddl/out/LambdaCube.IR.purs1590
1 files changed, 1590 insertions, 0 deletions
diff --git a/ddl/out/LambdaCube.IR.purs b/ddl/out/LambdaCube.IR.purs
new file mode 100644
index 0000000..459c1c8
--- /dev/null
+++ b/ddl/out/LambdaCube.IR.purs
@@ -0,0 +1,1590 @@
1-- generated file, do not modify!
2-- 2016-01-28T13:15:30.803775Z
3
4module LambdaCube.IR where
5import Prelude
6import Data.Generic
7import Data.Maybe (Maybe(..))
8import Data.StrMap (StrMap(..))
9import Data.Map (Map(..))
10import Data.List (List(..))
11import Linear
12
13import Data.Argonaut.Combinators ((~>), (:=), (.?))
14import Data.Argonaut.Core (jsonEmptyObject)
15import Data.Argonaut.Printer (printJson)
16import Data.Argonaut.Encode (EncodeJson, encodeJson)
17import Data.Argonaut.Decode (DecodeJson, decodeJson)
18
19
20type StreamName = Int
21
22type ProgramName = Int
23
24type TextureName = Int
25
26type SamplerName = Int
27
28type UniformName = String
29
30type SlotName = Int
31
32type FrameBufferComponent = Int
33
34type TextureUnit = Int
35
36type RenderTargetName = Int
37
38type TextureUnitMapping = StrMap TextureUnit
39
40data ArrayValue
41 = VBoolArray (Array Bool)
42 | VIntArray (Array Int32)
43 | VWordArray (Array Word32)
44 | VFloatArray (Array Float)
45
46data Value
47 = VBool Bool
48 | VV2B V2B
49 | VV3B V3B
50 | VV4B V4B
51 | VWord Word32
52 | VV2U V2U
53 | VV3U V3U
54 | VV4U V4U
55 | VInt Int32
56 | VV2I V2I
57 | VV3I V3I
58 | VV4I V4I
59 | VFloat Float
60 | VV2F V2F
61 | VV3F V3F
62 | VV4F V4F
63 | VM22F M22F
64 | VM23F M23F
65 | VM24F M24F
66 | VM32F M32F
67 | VM33F M33F
68 | VM34F M34F
69 | VM42F M42F
70 | VM43F M43F
71 | VM44F M44F
72
73data InputType
74 = Bool
75 | V2B
76 | V3B
77 | V4B
78 | Word
79 | V2U
80 | V3U
81 | V4U
82 | Int
83 | V2I
84 | V3I
85 | V4I
86 | Float
87 | V2F
88 | V3F
89 | V4F
90 | M22F
91 | M23F
92 | M24F
93 | M32F
94 | M33F
95 | M34F
96 | M42F
97 | M43F
98 | M44F
99 | STexture1D
100 | STexture2D
101 | STextureCube
102 | STexture1DArray
103 | STexture2DArray
104 | STexture2DRect
105 | FTexture1D
106 | FTexture2D
107 | FTexture3D
108 | FTextureCube
109 | FTexture1DArray
110 | FTexture2DArray
111 | FTexture2DMS
112 | FTexture2DMSArray
113 | FTextureBuffer
114 | FTexture2DRect
115 | ITexture1D
116 | ITexture2D
117 | ITexture3D
118 | ITextureCube
119 | ITexture1DArray
120 | ITexture2DArray
121 | ITexture2DMS
122 | ITexture2DMSArray
123 | ITextureBuffer
124 | ITexture2DRect
125 | UTexture1D
126 | UTexture2D
127 | UTexture3D
128 | UTextureCube
129 | UTexture1DArray
130 | UTexture2DArray
131 | UTexture2DMS
132 | UTexture2DMSArray
133 | UTextureBuffer
134 | UTexture2DRect
135
136data PointSpriteCoordOrigin
137 = LowerLeft
138 | UpperLeft
139
140data PointSize
141 = PointSize Float
142 | ProgramPointSize
143
144data PolygonOffset
145 = NoOffset
146 | Offset Float Float
147
148data FrontFace
149 = CCW
150 | CW
151
152data PolygonMode
153 = PolygonPoint PointSize
154 | PolygonLine Float
155 | PolygonFill
156
157data ProvokingVertex
158 = FirstVertex
159 | LastVertex
160
161data CullMode
162 = CullNone
163 | CullFront FrontFace
164 | CullBack FrontFace
165
166data ComparisonFunction
167 = Never
168 | Less
169 | Equal
170 | Lequal
171 | Greater
172 | Notequal
173 | Gequal
174 | Always
175
176type DepthFunction = ComparisonFunction
177
178data StencilOperation
179 = OpZero
180 | OpKeep
181 | OpReplace
182 | OpIncr
183 | OpIncrWrap
184 | OpDecr
185 | OpDecrWrap
186 | OpInvert
187
188data BlendEquation
189 = FuncAdd
190 | FuncSubtract
191 | FuncReverseSubtract
192 | Min
193 | Max
194
195data BlendingFactor
196 = Zero
197 | One
198 | SrcColor
199 | OneMinusSrcColor
200 | DstColor
201 | OneMinusDstColor
202 | SrcAlpha
203 | OneMinusSrcAlpha
204 | DstAlpha
205 | OneMinusDstAlpha
206 | ConstantColor
207 | OneMinusConstantColor
208 | ConstantAlpha
209 | OneMinusConstantAlpha
210 | SrcAlphaSaturate
211
212data LogicOperation
213 = Clear
214 | And
215 | AndReverse
216 | Copy
217 | AndInverted
218 | Noop
219 | Xor
220 | Or
221 | Nor
222 | Equiv
223 | Invert
224 | OrReverse
225 | CopyInverted
226 | OrInverted
227 | Nand
228 | Set
229
230data StencilOps
231 = StencilOps
232 { frontStencilOp :: StencilOperation
233 , backStencilOp :: StencilOperation
234 }
235
236
237data StencilTest
238 = StencilTest
239 { stencilComparision :: ComparisonFunction
240 , stencilReference :: Int32
241 , stencilMask :: Word32
242 }
243
244
245data StencilTests
246 = StencilTests StencilTest StencilTest
247
248data FetchPrimitive
249 = Points
250 | Lines
251 | Triangles
252 | LinesAdjacency
253 | TrianglesAdjacency
254
255data OutputPrimitive
256 = TrianglesOutput
257 | LinesOutput
258 | PointsOutput
259
260data ColorArity
261 = Red
262 | RG
263 | RGB
264 | RGBA
265
266data Blending
267 = NoBlending
268 | BlendLogicOp LogicOperation
269 | Blend
270 { colorEqSrc :: BlendEquation
271 , alphaEqSrc :: BlendEquation
272 , colorFSrc :: BlendingFactor
273 , colorFDst :: BlendingFactor
274 , alphaFSrc :: BlendingFactor
275 , alphaFDst :: BlendingFactor
276 , color :: V4F
277 }
278
279
280data RasterContext
281 = PointCtx PointSize Float PointSpriteCoordOrigin
282 | LineCtx Float ProvokingVertex
283 | TriangleCtx CullMode PolygonMode PolygonOffset ProvokingVertex
284
285data FragmentOperation
286 = DepthOp DepthFunction Bool
287 | StencilOp StencilTests StencilOps StencilOps
288 | ColorOp Blending Value
289
290data AccumulationContext
291 = AccumulationContext
292 { accViewportName :: Maybe String
293 , accOperations :: List FragmentOperation
294 }
295
296
297data TextureDataType
298 = FloatT ColorArity
299 | IntT ColorArity
300 | WordT ColorArity
301 | ShadowT
302
303data TextureType
304 = Texture1D TextureDataType Int
305 | Texture2D TextureDataType Int
306 | Texture3D TextureDataType
307 | TextureCube TextureDataType
308 | TextureRect TextureDataType
309 | Texture2DMS TextureDataType Int Int Bool
310 | TextureBuffer TextureDataType
311
312data MipMap
313 = Mip Int Int
314 | NoMip
315 | AutoMip Int Int
316
317data Filter
318 = Nearest
319 | Linear
320 | NearestMipmapNearest
321 | NearestMipmapLinear
322 | LinearMipmapNearest
323 | LinearMipmapLinear
324
325data EdgeMode
326 = Repeat
327 | MirroredRepeat
328 | ClampToEdge
329 | ClampToBorder
330
331data ImageSemantic
332 = Depth
333 | Stencil
334 | Color
335
336data ImageRef
337 = TextureImage TextureName Int (Maybe Int)
338 | Framebuffer ImageSemantic
339
340data ClearImage
341 = ClearImage
342 { imageSemantic :: ImageSemantic
343 , clearValue :: Value
344 }
345
346
347data Command
348 = SetRasterContext RasterContext
349 | SetAccumulationContext AccumulationContext
350 | SetRenderTarget RenderTargetName
351 | SetProgram ProgramName
352 | SetSamplerUniform UniformName TextureUnit
353 | SetTexture TextureUnit TextureName
354 | SetSampler TextureUnit (Maybe SamplerName)
355 | RenderSlot SlotName
356 | RenderStream StreamName
357 | ClearRenderTarget (Array ClearImage)
358 | GenerateMipMap TextureUnit
359 | SaveImage FrameBufferComponent ImageRef
360 | LoadImage ImageRef FrameBufferComponent
361
362data SamplerDescriptor
363 = SamplerDescriptor
364 { samplerWrapS :: EdgeMode
365 , samplerWrapT :: Maybe EdgeMode
366 , samplerWrapR :: Maybe EdgeMode
367 , samplerMinFilter :: Filter
368 , samplerMagFilter :: Filter
369 , samplerBorderColor :: Value
370 , samplerMinLod :: Maybe Float
371 , samplerMaxLod :: Maybe Float
372 , samplerLodBias :: Float
373 , samplerCompareFunc :: Maybe ComparisonFunction
374 }
375
376
377data TextureDescriptor
378 = TextureDescriptor
379 { textureType :: TextureType
380 , textureSize :: Value
381 , textureSemantic :: ImageSemantic
382 , textureSampler :: SamplerDescriptor
383 , textureBaseLevel :: Int
384 , textureMaxLevel :: Int
385 }
386
387
388data Parameter
389 = Parameter
390 { name :: String
391 , ty :: InputType
392 }
393
394
395data Program
396 = Program
397 { programUniforms :: StrMap InputType
398 , programStreams :: StrMap Parameter
399 , programInTextures :: StrMap InputType
400 , programOutput :: Array Parameter
401 , vertexShader :: String
402 , geometryShader :: Maybe String
403 , fragmentShader :: String
404 }
405
406
407data Slot
408 = Slot
409 { slotName :: String
410 , slotStreams :: StrMap InputType
411 , slotUniforms :: StrMap InputType
412 , slotPrimitive :: FetchPrimitive
413 , slotPrograms :: Array ProgramName
414 }
415
416
417data StreamData
418 = StreamData
419 { streamData :: StrMap ArrayValue
420 , streamType :: StrMap InputType
421 , streamPrimitive :: FetchPrimitive
422 , streamPrograms :: Array ProgramName
423 }
424
425
426data TargetItem
427 = TargetItem
428 { targetSemantic :: ImageSemantic
429 , targetRef :: Maybe ImageRef
430 }
431
432
433data RenderTarget
434 = RenderTarget
435 { renderTargets :: Array TargetItem
436 }
437
438
439data Backend
440 = WebGL1
441 | OpenGL33
442
443data Pipeline
444 = Pipeline
445 { backend :: Backend
446 , textures :: Array TextureDescriptor
447 , samplers :: Array SamplerDescriptor
448 , targets :: Array RenderTarget
449 , programs :: Array Program
450 , slots :: Array Slot
451 , streams :: Array StreamData
452 , commands :: Array Command
453 }
454
455
456
457derive instance genericInputType :: Generic InputType
458instance showInputType :: Show InputType where show = gShow
459instance eqInputType :: Eq InputType where eq = gEq
460
461derive instance genericFetchPrimitive :: Generic FetchPrimitive
462instance showFetchPrimitive :: Show FetchPrimitive where show = gShow
463instance eqFetchPrimitive :: Eq FetchPrimitive where eq = gEq
464
465derive instance genericColorArity :: Generic ColorArity
466instance showColorArity :: Show ColorArity where show = gShow
467instance eqColorArity :: Eq ColorArity where eq = gEq
468
469derive instance genericTextureDataType :: Generic TextureDataType
470instance showTextureDataType :: Show TextureDataType where show = gShow
471instance eqTextureDataType :: Eq TextureDataType where eq = gEq
472
473derive instance genericImageSemantic :: Generic ImageSemantic
474instance showImageSemantic :: Show ImageSemantic where show = gShow
475instance eqImageSemantic :: Eq ImageSemantic where eq = gEq
476
477derive instance genericPipeline :: Generic Pipeline
478instance showPipeline :: Show Pipeline where show = gShow
479instance eqPipeline :: Eq Pipeline where eq = gEq
480
481
482instance encodeJsonArrayValue :: EncodeJson ArrayValue where
483 encodeJson v = case v of
484 VBoolArray arg0 -> "tag" := "VBoolArray" ~> "arg0" := arg0 ~> jsonEmptyObject
485 VIntArray arg0 -> "tag" := "VIntArray" ~> "arg0" := arg0 ~> jsonEmptyObject
486 VWordArray arg0 -> "tag" := "VWordArray" ~> "arg0" := arg0 ~> jsonEmptyObject
487 VFloatArray arg0 -> "tag" := "VFloatArray" ~> "arg0" := arg0 ~> jsonEmptyObject
488
489instance decodeJsonArrayValue :: DecodeJson ArrayValue where
490 decodeJson json = do
491 obj <- decodeJson json
492 tag <- obj .? "tag"
493 case tag of
494 "VBoolArray" -> VBoolArray <$> obj .? "arg0"
495 "VIntArray" -> VIntArray <$> obj .? "arg0"
496 "VWordArray" -> VWordArray <$> obj .? "arg0"
497 "VFloatArray" -> VFloatArray <$> obj .? "arg0"
498
499instance encodeJsonValue :: EncodeJson Value where
500 encodeJson v = case v of
501 VBool arg0 -> "tag" := "VBool" ~> "arg0" := arg0 ~> jsonEmptyObject
502 VV2B arg0 -> "tag" := "VV2B" ~> "arg0" := arg0 ~> jsonEmptyObject
503 VV3B arg0 -> "tag" := "VV3B" ~> "arg0" := arg0 ~> jsonEmptyObject
504 VV4B arg0 -> "tag" := "VV4B" ~> "arg0" := arg0 ~> jsonEmptyObject
505 VWord arg0 -> "tag" := "VWord" ~> "arg0" := arg0 ~> jsonEmptyObject
506 VV2U arg0 -> "tag" := "VV2U" ~> "arg0" := arg0 ~> jsonEmptyObject
507 VV3U arg0 -> "tag" := "VV3U" ~> "arg0" := arg0 ~> jsonEmptyObject
508 VV4U arg0 -> "tag" := "VV4U" ~> "arg0" := arg0 ~> jsonEmptyObject
509 VInt arg0 -> "tag" := "VInt" ~> "arg0" := arg0 ~> jsonEmptyObject
510 VV2I arg0 -> "tag" := "VV2I" ~> "arg0" := arg0 ~> jsonEmptyObject
511 VV3I arg0 -> "tag" := "VV3I" ~> "arg0" := arg0 ~> jsonEmptyObject
512 VV4I arg0 -> "tag" := "VV4I" ~> "arg0" := arg0 ~> jsonEmptyObject
513 VFloat arg0 -> "tag" := "VFloat" ~> "arg0" := arg0 ~> jsonEmptyObject
514 VV2F arg0 -> "tag" := "VV2F" ~> "arg0" := arg0 ~> jsonEmptyObject
515 VV3F arg0 -> "tag" := "VV3F" ~> "arg0" := arg0 ~> jsonEmptyObject
516 VV4F arg0 -> "tag" := "VV4F" ~> "arg0" := arg0 ~> jsonEmptyObject
517 VM22F arg0 -> "tag" := "VM22F" ~> "arg0" := arg0 ~> jsonEmptyObject
518 VM23F arg0 -> "tag" := "VM23F" ~> "arg0" := arg0 ~> jsonEmptyObject
519 VM24F arg0 -> "tag" := "VM24F" ~> "arg0" := arg0 ~> jsonEmptyObject
520 VM32F arg0 -> "tag" := "VM32F" ~> "arg0" := arg0 ~> jsonEmptyObject
521 VM33F arg0 -> "tag" := "VM33F" ~> "arg0" := arg0 ~> jsonEmptyObject
522 VM34F arg0 -> "tag" := "VM34F" ~> "arg0" := arg0 ~> jsonEmptyObject
523 VM42F arg0 -> "tag" := "VM42F" ~> "arg0" := arg0 ~> jsonEmptyObject
524 VM43F arg0 -> "tag" := "VM43F" ~> "arg0" := arg0 ~> jsonEmptyObject
525 VM44F arg0 -> "tag" := "VM44F" ~> "arg0" := arg0 ~> jsonEmptyObject
526
527instance decodeJsonValue :: DecodeJson Value where
528 decodeJson json = do
529 obj <- decodeJson json
530 tag <- obj .? "tag"
531 case tag of
532 "VBool" -> VBool <$> obj .? "arg0"
533 "VV2B" -> VV2B <$> obj .? "arg0"
534 "VV3B" -> VV3B <$> obj .? "arg0"
535 "VV4B" -> VV4B <$> obj .? "arg0"
536 "VWord" -> VWord <$> obj .? "arg0"
537 "VV2U" -> VV2U <$> obj .? "arg0"
538 "VV3U" -> VV3U <$> obj .? "arg0"
539 "VV4U" -> VV4U <$> obj .? "arg0"
540 "VInt" -> VInt <$> obj .? "arg0"
541 "VV2I" -> VV2I <$> obj .? "arg0"
542 "VV3I" -> VV3I <$> obj .? "arg0"
543 "VV4I" -> VV4I <$> obj .? "arg0"
544 "VFloat" -> VFloat <$> obj .? "arg0"
545 "VV2F" -> VV2F <$> obj .? "arg0"
546 "VV3F" -> VV3F <$> obj .? "arg0"
547 "VV4F" -> VV4F <$> obj .? "arg0"
548 "VM22F" -> VM22F <$> obj .? "arg0"
549 "VM23F" -> VM23F <$> obj .? "arg0"
550 "VM24F" -> VM24F <$> obj .? "arg0"
551 "VM32F" -> VM32F <$> obj .? "arg0"
552 "VM33F" -> VM33F <$> obj .? "arg0"
553 "VM34F" -> VM34F <$> obj .? "arg0"
554 "VM42F" -> VM42F <$> obj .? "arg0"
555 "VM43F" -> VM43F <$> obj .? "arg0"
556 "VM44F" -> VM44F <$> obj .? "arg0"
557
558instance encodeJsonInputType :: EncodeJson InputType where
559 encodeJson v = case v of
560 Bool -> "tag" := "Bool" ~> jsonEmptyObject
561 V2B -> "tag" := "V2B" ~> jsonEmptyObject
562 V3B -> "tag" := "V3B" ~> jsonEmptyObject
563 V4B -> "tag" := "V4B" ~> jsonEmptyObject
564 Word -> "tag" := "Word" ~> jsonEmptyObject
565 V2U -> "tag" := "V2U" ~> jsonEmptyObject
566 V3U -> "tag" := "V3U" ~> jsonEmptyObject
567 V4U -> "tag" := "V4U" ~> jsonEmptyObject
568 Int -> "tag" := "Int" ~> jsonEmptyObject
569 V2I -> "tag" := "V2I" ~> jsonEmptyObject
570 V3I -> "tag" := "V3I" ~> jsonEmptyObject
571 V4I -> "tag" := "V4I" ~> jsonEmptyObject
572 Float -> "tag" := "Float" ~> jsonEmptyObject
573 V2F -> "tag" := "V2F" ~> jsonEmptyObject
574 V3F -> "tag" := "V3F" ~> jsonEmptyObject
575 V4F -> "tag" := "V4F" ~> jsonEmptyObject
576 M22F -> "tag" := "M22F" ~> jsonEmptyObject
577 M23F -> "tag" := "M23F" ~> jsonEmptyObject
578 M24F -> "tag" := "M24F" ~> jsonEmptyObject
579 M32F -> "tag" := "M32F" ~> jsonEmptyObject
580 M33F -> "tag" := "M33F" ~> jsonEmptyObject
581 M34F -> "tag" := "M34F" ~> jsonEmptyObject
582 M42F -> "tag" := "M42F" ~> jsonEmptyObject
583 M43F -> "tag" := "M43F" ~> jsonEmptyObject
584 M44F -> "tag" := "M44F" ~> jsonEmptyObject
585 STexture1D -> "tag" := "STexture1D" ~> jsonEmptyObject
586 STexture2D -> "tag" := "STexture2D" ~> jsonEmptyObject
587 STextureCube -> "tag" := "STextureCube" ~> jsonEmptyObject
588 STexture1DArray -> "tag" := "STexture1DArray" ~> jsonEmptyObject
589 STexture2DArray -> "tag" := "STexture2DArray" ~> jsonEmptyObject
590 STexture2DRect -> "tag" := "STexture2DRect" ~> jsonEmptyObject
591 FTexture1D -> "tag" := "FTexture1D" ~> jsonEmptyObject
592 FTexture2D -> "tag" := "FTexture2D" ~> jsonEmptyObject
593 FTexture3D -> "tag" := "FTexture3D" ~> jsonEmptyObject
594 FTextureCube -> "tag" := "FTextureCube" ~> jsonEmptyObject
595 FTexture1DArray -> "tag" := "FTexture1DArray" ~> jsonEmptyObject
596 FTexture2DArray -> "tag" := "FTexture2DArray" ~> jsonEmptyObject
597 FTexture2DMS -> "tag" := "FTexture2DMS" ~> jsonEmptyObject
598 FTexture2DMSArray -> "tag" := "FTexture2DMSArray" ~> jsonEmptyObject
599 FTextureBuffer -> "tag" := "FTextureBuffer" ~> jsonEmptyObject
600 FTexture2DRect -> "tag" := "FTexture2DRect" ~> jsonEmptyObject
601 ITexture1D -> "tag" := "ITexture1D" ~> jsonEmptyObject
602 ITexture2D -> "tag" := "ITexture2D" ~> jsonEmptyObject
603 ITexture3D -> "tag" := "ITexture3D" ~> jsonEmptyObject
604 ITextureCube -> "tag" := "ITextureCube" ~> jsonEmptyObject
605 ITexture1DArray -> "tag" := "ITexture1DArray" ~> jsonEmptyObject
606 ITexture2DArray -> "tag" := "ITexture2DArray" ~> jsonEmptyObject
607 ITexture2DMS -> "tag" := "ITexture2DMS" ~> jsonEmptyObject
608 ITexture2DMSArray -> "tag" := "ITexture2DMSArray" ~> jsonEmptyObject
609 ITextureBuffer -> "tag" := "ITextureBuffer" ~> jsonEmptyObject
610 ITexture2DRect -> "tag" := "ITexture2DRect" ~> jsonEmptyObject
611 UTexture1D -> "tag" := "UTexture1D" ~> jsonEmptyObject
612 UTexture2D -> "tag" := "UTexture2D" ~> jsonEmptyObject
613 UTexture3D -> "tag" := "UTexture3D" ~> jsonEmptyObject
614 UTextureCube -> "tag" := "UTextureCube" ~> jsonEmptyObject
615 UTexture1DArray -> "tag" := "UTexture1DArray" ~> jsonEmptyObject
616 UTexture2DArray -> "tag" := "UTexture2DArray" ~> jsonEmptyObject
617 UTexture2DMS -> "tag" := "UTexture2DMS" ~> jsonEmptyObject
618 UTexture2DMSArray -> "tag" := "UTexture2DMSArray" ~> jsonEmptyObject
619 UTextureBuffer -> "tag" := "UTextureBuffer" ~> jsonEmptyObject
620 UTexture2DRect -> "tag" := "UTexture2DRect" ~> jsonEmptyObject
621
622instance decodeJsonInputType :: DecodeJson InputType where
623 decodeJson json = do
624 obj <- decodeJson json
625 tag <- obj .? "tag"
626 case tag of
627 "Bool" -> pure Bool
628 "V2B" -> pure V2B
629 "V3B" -> pure V3B
630 "V4B" -> pure V4B
631 "Word" -> pure Word
632 "V2U" -> pure V2U
633 "V3U" -> pure V3U
634 "V4U" -> pure V4U
635 "Int" -> pure Int
636 "V2I" -> pure V2I
637 "V3I" -> pure V3I
638 "V4I" -> pure V4I
639 "Float" -> pure Float
640 "V2F" -> pure V2F
641 "V3F" -> pure V3F
642 "V4F" -> pure V4F
643 "M22F" -> pure M22F
644 "M23F" -> pure M23F
645 "M24F" -> pure M24F
646 "M32F" -> pure M32F
647 "M33F" -> pure M33F
648 "M34F" -> pure M34F
649 "M42F" -> pure M42F
650 "M43F" -> pure M43F
651 "M44F" -> pure M44F
652 "STexture1D" -> pure STexture1D
653 "STexture2D" -> pure STexture2D
654 "STextureCube" -> pure STextureCube
655 "STexture1DArray" -> pure STexture1DArray
656 "STexture2DArray" -> pure STexture2DArray
657 "STexture2DRect" -> pure STexture2DRect
658 "FTexture1D" -> pure FTexture1D
659 "FTexture2D" -> pure FTexture2D
660 "FTexture3D" -> pure FTexture3D
661 "FTextureCube" -> pure FTextureCube
662 "FTexture1DArray" -> pure FTexture1DArray
663 "FTexture2DArray" -> pure FTexture2DArray
664 "FTexture2DMS" -> pure FTexture2DMS
665 "FTexture2DMSArray" -> pure FTexture2DMSArray
666 "FTextureBuffer" -> pure FTextureBuffer
667 "FTexture2DRect" -> pure FTexture2DRect
668 "ITexture1D" -> pure ITexture1D
669 "ITexture2D" -> pure ITexture2D
670 "ITexture3D" -> pure ITexture3D
671 "ITextureCube" -> pure ITextureCube
672 "ITexture1DArray" -> pure ITexture1DArray
673 "ITexture2DArray" -> pure ITexture2DArray
674 "ITexture2DMS" -> pure ITexture2DMS
675 "ITexture2DMSArray" -> pure ITexture2DMSArray
676 "ITextureBuffer" -> pure ITextureBuffer
677 "ITexture2DRect" -> pure ITexture2DRect
678 "UTexture1D" -> pure UTexture1D
679 "UTexture2D" -> pure UTexture2D
680 "UTexture3D" -> pure UTexture3D
681 "UTextureCube" -> pure UTextureCube
682 "UTexture1DArray" -> pure UTexture1DArray
683 "UTexture2DArray" -> pure UTexture2DArray
684 "UTexture2DMS" -> pure UTexture2DMS
685 "UTexture2DMSArray" -> pure UTexture2DMSArray
686 "UTextureBuffer" -> pure UTextureBuffer
687 "UTexture2DRect" -> pure UTexture2DRect
688
689instance encodeJsonPointSpriteCoordOrigin :: EncodeJson PointSpriteCoordOrigin where
690 encodeJson v = case v of
691 LowerLeft -> "tag" := "LowerLeft" ~> jsonEmptyObject
692 UpperLeft -> "tag" := "UpperLeft" ~> jsonEmptyObject
693
694instance decodeJsonPointSpriteCoordOrigin :: DecodeJson PointSpriteCoordOrigin where
695 decodeJson json = do
696 obj <- decodeJson json
697 tag <- obj .? "tag"
698 case tag of
699 "LowerLeft" -> pure LowerLeft
700 "UpperLeft" -> pure UpperLeft
701
702instance encodeJsonPointSize :: EncodeJson PointSize where
703 encodeJson v = case v of
704 PointSize arg0 -> "tag" := "PointSize" ~> "arg0" := arg0 ~> jsonEmptyObject
705 ProgramPointSize -> "tag" := "ProgramPointSize" ~> jsonEmptyObject
706
707instance decodeJsonPointSize :: DecodeJson PointSize where
708 decodeJson json = do
709 obj <- decodeJson json
710 tag <- obj .? "tag"
711 case tag of
712 "PointSize" -> PointSize <$> obj .? "arg0"
713 "ProgramPointSize" -> pure ProgramPointSize
714
715instance encodeJsonPolygonOffset :: EncodeJson PolygonOffset where
716 encodeJson v = case v of
717 NoOffset -> "tag" := "NoOffset" ~> jsonEmptyObject
718 Offset arg0 arg1 -> "tag" := "Offset" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
719
720instance decodeJsonPolygonOffset :: DecodeJson PolygonOffset where
721 decodeJson json = do
722 obj <- decodeJson json
723 tag <- obj .? "tag"
724 case tag of
725 "NoOffset" -> pure NoOffset
726 "Offset" -> Offset <$> obj .? "arg0" <*> obj .? "arg1"
727
728instance encodeJsonFrontFace :: EncodeJson FrontFace where
729 encodeJson v = case v of
730 CCW -> "tag" := "CCW" ~> jsonEmptyObject
731 CW -> "tag" := "CW" ~> jsonEmptyObject
732
733instance decodeJsonFrontFace :: DecodeJson FrontFace where
734 decodeJson json = do
735 obj <- decodeJson json
736 tag <- obj .? "tag"
737 case tag of
738 "CCW" -> pure CCW
739 "CW" -> pure CW
740
741instance encodeJsonPolygonMode :: EncodeJson PolygonMode where
742 encodeJson v = case v of
743 PolygonPoint arg0 -> "tag" := "PolygonPoint" ~> "arg0" := arg0 ~> jsonEmptyObject
744 PolygonLine arg0 -> "tag" := "PolygonLine" ~> "arg0" := arg0 ~> jsonEmptyObject
745 PolygonFill -> "tag" := "PolygonFill" ~> jsonEmptyObject
746
747instance decodeJsonPolygonMode :: DecodeJson PolygonMode where
748 decodeJson json = do
749 obj <- decodeJson json
750 tag <- obj .? "tag"
751 case tag of
752 "PolygonPoint" -> PolygonPoint <$> obj .? "arg0"
753 "PolygonLine" -> PolygonLine <$> obj .? "arg0"
754 "PolygonFill" -> pure PolygonFill
755
756instance encodeJsonProvokingVertex :: EncodeJson ProvokingVertex where
757 encodeJson v = case v of
758 FirstVertex -> "tag" := "FirstVertex" ~> jsonEmptyObject
759 LastVertex -> "tag" := "LastVertex" ~> jsonEmptyObject
760
761instance decodeJsonProvokingVertex :: DecodeJson ProvokingVertex where
762 decodeJson json = do
763 obj <- decodeJson json
764 tag <- obj .? "tag"
765 case tag of
766 "FirstVertex" -> pure FirstVertex
767 "LastVertex" -> pure LastVertex
768
769instance encodeJsonCullMode :: EncodeJson CullMode where
770 encodeJson v = case v of
771 CullNone -> "tag" := "CullNone" ~> jsonEmptyObject
772 CullFront arg0 -> "tag" := "CullFront" ~> "arg0" := arg0 ~> jsonEmptyObject
773 CullBack arg0 -> "tag" := "CullBack" ~> "arg0" := arg0 ~> jsonEmptyObject
774
775instance decodeJsonCullMode :: DecodeJson CullMode where
776 decodeJson json = do
777 obj <- decodeJson json
778 tag <- obj .? "tag"
779 case tag of
780 "CullNone" -> pure CullNone
781 "CullFront" -> CullFront <$> obj .? "arg0"
782 "CullBack" -> CullBack <$> obj .? "arg0"
783
784instance encodeJsonComparisonFunction :: EncodeJson ComparisonFunction where
785 encodeJson v = case v of
786 Never -> "tag" := "Never" ~> jsonEmptyObject
787 Less -> "tag" := "Less" ~> jsonEmptyObject
788 Equal -> "tag" := "Equal" ~> jsonEmptyObject
789 Lequal -> "tag" := "Lequal" ~> jsonEmptyObject
790 Greater -> "tag" := "Greater" ~> jsonEmptyObject
791 Notequal -> "tag" := "Notequal" ~> jsonEmptyObject
792 Gequal -> "tag" := "Gequal" ~> jsonEmptyObject
793 Always -> "tag" := "Always" ~> jsonEmptyObject
794
795instance decodeJsonComparisonFunction :: DecodeJson ComparisonFunction where
796 decodeJson json = do
797 obj <- decodeJson json
798 tag <- obj .? "tag"
799 case tag of
800 "Never" -> pure Never
801 "Less" -> pure Less
802 "Equal" -> pure Equal
803 "Lequal" -> pure Lequal
804 "Greater" -> pure Greater
805 "Notequal" -> pure Notequal
806 "Gequal" -> pure Gequal
807 "Always" -> pure Always
808
809instance encodeJsonStencilOperation :: EncodeJson StencilOperation where
810 encodeJson v = case v of
811 OpZero -> "tag" := "OpZero" ~> jsonEmptyObject
812 OpKeep -> "tag" := "OpKeep" ~> jsonEmptyObject
813 OpReplace -> "tag" := "OpReplace" ~> jsonEmptyObject
814 OpIncr -> "tag" := "OpIncr" ~> jsonEmptyObject
815 OpIncrWrap -> "tag" := "OpIncrWrap" ~> jsonEmptyObject
816 OpDecr -> "tag" := "OpDecr" ~> jsonEmptyObject
817 OpDecrWrap -> "tag" := "OpDecrWrap" ~> jsonEmptyObject
818 OpInvert -> "tag" := "OpInvert" ~> jsonEmptyObject
819
820instance decodeJsonStencilOperation :: DecodeJson StencilOperation where
821 decodeJson json = do
822 obj <- decodeJson json
823 tag <- obj .? "tag"
824 case tag of
825 "OpZero" -> pure OpZero
826 "OpKeep" -> pure OpKeep
827 "OpReplace" -> pure OpReplace
828 "OpIncr" -> pure OpIncr
829 "OpIncrWrap" -> pure OpIncrWrap
830 "OpDecr" -> pure OpDecr
831 "OpDecrWrap" -> pure OpDecrWrap
832 "OpInvert" -> pure OpInvert
833
834instance encodeJsonBlendEquation :: EncodeJson BlendEquation where
835 encodeJson v = case v of
836 FuncAdd -> "tag" := "FuncAdd" ~> jsonEmptyObject
837 FuncSubtract -> "tag" := "FuncSubtract" ~> jsonEmptyObject
838 FuncReverseSubtract -> "tag" := "FuncReverseSubtract" ~> jsonEmptyObject
839 Min -> "tag" := "Min" ~> jsonEmptyObject
840 Max -> "tag" := "Max" ~> jsonEmptyObject
841
842instance decodeJsonBlendEquation :: DecodeJson BlendEquation where
843 decodeJson json = do
844 obj <- decodeJson json
845 tag <- obj .? "tag"
846 case tag of
847 "FuncAdd" -> pure FuncAdd
848 "FuncSubtract" -> pure FuncSubtract
849 "FuncReverseSubtract" -> pure FuncReverseSubtract
850 "Min" -> pure Min
851 "Max" -> pure Max
852
853instance encodeJsonBlendingFactor :: EncodeJson BlendingFactor where
854 encodeJson v = case v of
855 Zero -> "tag" := "Zero" ~> jsonEmptyObject
856 One -> "tag" := "One" ~> jsonEmptyObject
857 SrcColor -> "tag" := "SrcColor" ~> jsonEmptyObject
858 OneMinusSrcColor -> "tag" := "OneMinusSrcColor" ~> jsonEmptyObject
859 DstColor -> "tag" := "DstColor" ~> jsonEmptyObject
860 OneMinusDstColor -> "tag" := "OneMinusDstColor" ~> jsonEmptyObject
861 SrcAlpha -> "tag" := "SrcAlpha" ~> jsonEmptyObject
862 OneMinusSrcAlpha -> "tag" := "OneMinusSrcAlpha" ~> jsonEmptyObject
863 DstAlpha -> "tag" := "DstAlpha" ~> jsonEmptyObject
864 OneMinusDstAlpha -> "tag" := "OneMinusDstAlpha" ~> jsonEmptyObject
865 ConstantColor -> "tag" := "ConstantColor" ~> jsonEmptyObject
866 OneMinusConstantColor -> "tag" := "OneMinusConstantColor" ~> jsonEmptyObject
867 ConstantAlpha -> "tag" := "ConstantAlpha" ~> jsonEmptyObject
868 OneMinusConstantAlpha -> "tag" := "OneMinusConstantAlpha" ~> jsonEmptyObject
869 SrcAlphaSaturate -> "tag" := "SrcAlphaSaturate" ~> jsonEmptyObject
870
871instance decodeJsonBlendingFactor :: DecodeJson BlendingFactor where
872 decodeJson json = do
873 obj <- decodeJson json
874 tag <- obj .? "tag"
875 case tag of
876 "Zero" -> pure Zero
877 "One" -> pure One
878 "SrcColor" -> pure SrcColor
879 "OneMinusSrcColor" -> pure OneMinusSrcColor
880 "DstColor" -> pure DstColor
881 "OneMinusDstColor" -> pure OneMinusDstColor
882 "SrcAlpha" -> pure SrcAlpha
883 "OneMinusSrcAlpha" -> pure OneMinusSrcAlpha
884 "DstAlpha" -> pure DstAlpha
885 "OneMinusDstAlpha" -> pure OneMinusDstAlpha
886 "ConstantColor" -> pure ConstantColor
887 "OneMinusConstantColor" -> pure OneMinusConstantColor
888 "ConstantAlpha" -> pure ConstantAlpha
889 "OneMinusConstantAlpha" -> pure OneMinusConstantAlpha
890 "SrcAlphaSaturate" -> pure SrcAlphaSaturate
891
892instance encodeJsonLogicOperation :: EncodeJson LogicOperation where
893 encodeJson v = case v of
894 Clear -> "tag" := "Clear" ~> jsonEmptyObject
895 And -> "tag" := "And" ~> jsonEmptyObject
896 AndReverse -> "tag" := "AndReverse" ~> jsonEmptyObject
897 Copy -> "tag" := "Copy" ~> jsonEmptyObject
898 AndInverted -> "tag" := "AndInverted" ~> jsonEmptyObject
899 Noop -> "tag" := "Noop" ~> jsonEmptyObject
900 Xor -> "tag" := "Xor" ~> jsonEmptyObject
901 Or -> "tag" := "Or" ~> jsonEmptyObject
902 Nor -> "tag" := "Nor" ~> jsonEmptyObject
903 Equiv -> "tag" := "Equiv" ~> jsonEmptyObject
904 Invert -> "tag" := "Invert" ~> jsonEmptyObject
905 OrReverse -> "tag" := "OrReverse" ~> jsonEmptyObject
906 CopyInverted -> "tag" := "CopyInverted" ~> jsonEmptyObject
907 OrInverted -> "tag" := "OrInverted" ~> jsonEmptyObject
908 Nand -> "tag" := "Nand" ~> jsonEmptyObject
909 Set -> "tag" := "Set" ~> jsonEmptyObject
910
911instance decodeJsonLogicOperation :: DecodeJson LogicOperation where
912 decodeJson json = do
913 obj <- decodeJson json
914 tag <- obj .? "tag"
915 case tag of
916 "Clear" -> pure Clear
917 "And" -> pure And
918 "AndReverse" -> pure AndReverse
919 "Copy" -> pure Copy
920 "AndInverted" -> pure AndInverted
921 "Noop" -> pure Noop
922 "Xor" -> pure Xor
923 "Or" -> pure Or
924 "Nor" -> pure Nor
925 "Equiv" -> pure Equiv
926 "Invert" -> pure Invert
927 "OrReverse" -> pure OrReverse
928 "CopyInverted" -> pure CopyInverted
929 "OrInverted" -> pure OrInverted
930 "Nand" -> pure Nand
931 "Set" -> pure Set
932
933instance encodeJsonStencilOps :: EncodeJson StencilOps where
934 encodeJson v = case v of
935 StencilOps r ->
936 "tag" := "StencilOps" ~>
937 "frontStencilOp" := r.frontStencilOp ~>
938 "backStencilOp" := r.backStencilOp ~>
939 jsonEmptyObject
940
941instance decodeJsonStencilOps :: DecodeJson StencilOps where
942 decodeJson json = do
943 obj <- decodeJson json
944 tag <- obj .? "tag"
945 case tag of
946 "StencilOps" -> do
947 frontStencilOp <- obj .? "frontStencilOp"
948 backStencilOp <- obj .? "backStencilOp"
949 pure $ StencilOps
950 { frontStencilOp:frontStencilOp
951 , backStencilOp:backStencilOp
952 }
953
954instance encodeJsonStencilTest :: EncodeJson StencilTest where
955 encodeJson v = case v of
956 StencilTest r ->
957 "tag" := "StencilTest" ~>
958 "stencilComparision" := r.stencilComparision ~>
959 "stencilReference" := r.stencilReference ~>
960 "stencilMask" := r.stencilMask ~>
961 jsonEmptyObject
962
963instance decodeJsonStencilTest :: DecodeJson StencilTest where
964 decodeJson json = do
965 obj <- decodeJson json
966 tag <- obj .? "tag"
967 case tag of
968 "StencilTest" -> do
969 stencilComparision <- obj .? "stencilComparision"
970 stencilReference <- obj .? "stencilReference"
971 stencilMask <- obj .? "stencilMask"
972 pure $ StencilTest
973 { stencilComparision:stencilComparision
974 , stencilReference:stencilReference
975 , stencilMask:stencilMask
976 }
977
978instance encodeJsonStencilTests :: EncodeJson StencilTests where
979 encodeJson v = case v of
980 StencilTests arg0 arg1 -> "tag" := "StencilTests" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
981
982instance decodeJsonStencilTests :: DecodeJson StencilTests where
983 decodeJson json = do
984 obj <- decodeJson json
985 tag <- obj .? "tag"
986 case tag of
987 "StencilTests" -> StencilTests <$> obj .? "arg0" <*> obj .? "arg1"
988
989instance encodeJsonFetchPrimitive :: EncodeJson FetchPrimitive where
990 encodeJson v = case v of
991 Points -> "tag" := "Points" ~> jsonEmptyObject
992 Lines -> "tag" := "Lines" ~> jsonEmptyObject
993 Triangles -> "tag" := "Triangles" ~> jsonEmptyObject
994 LinesAdjacency -> "tag" := "LinesAdjacency" ~> jsonEmptyObject
995 TrianglesAdjacency -> "tag" := "TrianglesAdjacency" ~> jsonEmptyObject
996
997instance decodeJsonFetchPrimitive :: DecodeJson FetchPrimitive where
998 decodeJson json = do
999 obj <- decodeJson json
1000 tag <- obj .? "tag"
1001 case tag of
1002 "Points" -> pure Points
1003 "Lines" -> pure Lines
1004 "Triangles" -> pure Triangles
1005 "LinesAdjacency" -> pure LinesAdjacency
1006 "TrianglesAdjacency" -> pure TrianglesAdjacency
1007
1008instance encodeJsonOutputPrimitive :: EncodeJson OutputPrimitive where
1009 encodeJson v = case v of
1010 TrianglesOutput -> "tag" := "TrianglesOutput" ~> jsonEmptyObject
1011 LinesOutput -> "tag" := "LinesOutput" ~> jsonEmptyObject
1012 PointsOutput -> "tag" := "PointsOutput" ~> jsonEmptyObject
1013
1014instance decodeJsonOutputPrimitive :: DecodeJson OutputPrimitive where
1015 decodeJson json = do
1016 obj <- decodeJson json
1017 tag <- obj .? "tag"
1018 case tag of
1019 "TrianglesOutput" -> pure TrianglesOutput
1020 "LinesOutput" -> pure LinesOutput
1021 "PointsOutput" -> pure PointsOutput
1022
1023instance encodeJsonColorArity :: EncodeJson ColorArity where
1024 encodeJson v = case v of
1025 Red -> "tag" := "Red" ~> jsonEmptyObject
1026 RG -> "tag" := "RG" ~> jsonEmptyObject
1027 RGB -> "tag" := "RGB" ~> jsonEmptyObject
1028 RGBA -> "tag" := "RGBA" ~> jsonEmptyObject
1029
1030instance decodeJsonColorArity :: DecodeJson ColorArity where
1031 decodeJson json = do
1032 obj <- decodeJson json
1033 tag <- obj .? "tag"
1034 case tag of
1035 "Red" -> pure Red
1036 "RG" -> pure RG
1037 "RGB" -> pure RGB
1038 "RGBA" -> pure RGBA
1039
1040instance encodeJsonBlending :: EncodeJson Blending where
1041 encodeJson v = case v of
1042 NoBlending -> "tag" := "NoBlending" ~> jsonEmptyObject
1043 BlendLogicOp arg0 -> "tag" := "BlendLogicOp" ~> "arg0" := arg0 ~> jsonEmptyObject
1044 Blend r ->
1045 "tag" := "Blend" ~>
1046 "colorEqSrc" := r.colorEqSrc ~>
1047 "alphaEqSrc" := r.alphaEqSrc ~>
1048 "colorFSrc" := r.colorFSrc ~>
1049 "colorFDst" := r.colorFDst ~>
1050 "alphaFSrc" := r.alphaFSrc ~>
1051 "alphaFDst" := r.alphaFDst ~>
1052 "color" := r.color ~>
1053 jsonEmptyObject
1054
1055instance decodeJsonBlending :: DecodeJson Blending where
1056 decodeJson json = do
1057 obj <- decodeJson json
1058 tag <- obj .? "tag"
1059 case tag of
1060 "NoBlending" -> pure NoBlending
1061 "BlendLogicOp" -> BlendLogicOp <$> obj .? "arg0"
1062 "Blend" -> do
1063 colorEqSrc <- obj .? "colorEqSrc"
1064 alphaEqSrc <- obj .? "alphaEqSrc"
1065 colorFSrc <- obj .? "colorFSrc"
1066 colorFDst <- obj .? "colorFDst"
1067 alphaFSrc <- obj .? "alphaFSrc"
1068 alphaFDst <- obj .? "alphaFDst"
1069 color <- obj .? "color"
1070 pure $ Blend
1071 { colorEqSrc:colorEqSrc
1072 , alphaEqSrc:alphaEqSrc
1073 , colorFSrc:colorFSrc
1074 , colorFDst:colorFDst
1075 , alphaFSrc:alphaFSrc
1076 , alphaFDst:alphaFDst
1077 , color:color
1078 }
1079
1080instance encodeJsonRasterContext :: EncodeJson RasterContext where
1081 encodeJson v = case v of
1082 PointCtx arg0 arg1 arg2 -> "tag" := "PointCtx" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> "arg2" := arg2 ~> jsonEmptyObject
1083 LineCtx arg0 arg1 -> "tag" := "LineCtx" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1084 TriangleCtx arg0 arg1 arg2 arg3 -> "tag" := "TriangleCtx" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> "arg2" := arg2 ~> "arg3" := arg3 ~> jsonEmptyObject
1085
1086instance decodeJsonRasterContext :: DecodeJson RasterContext where
1087 decodeJson json = do
1088 obj <- decodeJson json
1089 tag <- obj .? "tag"
1090 case tag of
1091 "PointCtx" -> PointCtx <$> obj .? "arg0" <*> obj .? "arg1" <*> obj .? "arg2"
1092 "LineCtx" -> LineCtx <$> obj .? "arg0" <*> obj .? "arg1"
1093 "TriangleCtx" -> TriangleCtx <$> obj .? "arg0" <*> obj .? "arg1" <*> obj .? "arg2" <*> obj .? "arg3"
1094
1095instance encodeJsonFragmentOperation :: EncodeJson FragmentOperation where
1096 encodeJson v = case v of
1097 DepthOp arg0 arg1 -> "tag" := "DepthOp" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1098 StencilOp arg0 arg1 arg2 -> "tag" := "StencilOp" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> "arg2" := arg2 ~> jsonEmptyObject
1099 ColorOp arg0 arg1 -> "tag" := "ColorOp" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1100
1101instance decodeJsonFragmentOperation :: DecodeJson FragmentOperation where
1102 decodeJson json = do
1103 obj <- decodeJson json
1104 tag <- obj .? "tag"
1105 case tag of
1106 "DepthOp" -> DepthOp <$> obj .? "arg0" <*> obj .? "arg1"
1107 "StencilOp" -> StencilOp <$> obj .? "arg0" <*> obj .? "arg1" <*> obj .? "arg2"
1108 "ColorOp" -> ColorOp <$> obj .? "arg0" <*> obj .? "arg1"
1109
1110instance encodeJsonAccumulationContext :: EncodeJson AccumulationContext where
1111 encodeJson v = case v of
1112 AccumulationContext r ->
1113 "tag" := "AccumulationContext" ~>
1114 "accViewportName" := r.accViewportName ~>
1115 "accOperations" := r.accOperations ~>
1116 jsonEmptyObject
1117
1118instance decodeJsonAccumulationContext :: DecodeJson AccumulationContext where
1119 decodeJson json = do
1120 obj <- decodeJson json
1121 tag <- obj .? "tag"
1122 case tag of
1123 "AccumulationContext" -> do
1124 accViewportName <- obj .? "accViewportName"
1125 accOperations <- obj .? "accOperations"
1126 pure $ AccumulationContext
1127 { accViewportName:accViewportName
1128 , accOperations:accOperations
1129 }
1130
1131instance encodeJsonTextureDataType :: EncodeJson TextureDataType where
1132 encodeJson v = case v of
1133 FloatT arg0 -> "tag" := "FloatT" ~> "arg0" := arg0 ~> jsonEmptyObject
1134 IntT arg0 -> "tag" := "IntT" ~> "arg0" := arg0 ~> jsonEmptyObject
1135 WordT arg0 -> "tag" := "WordT" ~> "arg0" := arg0 ~> jsonEmptyObject
1136 ShadowT -> "tag" := "ShadowT" ~> jsonEmptyObject
1137
1138instance decodeJsonTextureDataType :: DecodeJson TextureDataType where
1139 decodeJson json = do
1140 obj <- decodeJson json
1141 tag <- obj .? "tag"
1142 case tag of
1143 "FloatT" -> FloatT <$> obj .? "arg0"
1144 "IntT" -> IntT <$> obj .? "arg0"
1145 "WordT" -> WordT <$> obj .? "arg0"
1146 "ShadowT" -> pure ShadowT
1147
1148instance encodeJsonTextureType :: EncodeJson TextureType where
1149 encodeJson v = case v of
1150 Texture1D arg0 arg1 -> "tag" := "Texture1D" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1151 Texture2D arg0 arg1 -> "tag" := "Texture2D" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1152 Texture3D arg0 -> "tag" := "Texture3D" ~> "arg0" := arg0 ~> jsonEmptyObject
1153 TextureCube arg0 -> "tag" := "TextureCube" ~> "arg0" := arg0 ~> jsonEmptyObject
1154 TextureRect arg0 -> "tag" := "TextureRect" ~> "arg0" := arg0 ~> jsonEmptyObject
1155 Texture2DMS arg0 arg1 arg2 arg3 -> "tag" := "Texture2DMS" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> "arg2" := arg2 ~> "arg3" := arg3 ~> jsonEmptyObject
1156 TextureBuffer arg0 -> "tag" := "TextureBuffer" ~> "arg0" := arg0 ~> jsonEmptyObject
1157
1158instance decodeJsonTextureType :: DecodeJson TextureType where
1159 decodeJson json = do
1160 obj <- decodeJson json
1161 tag <- obj .? "tag"
1162 case tag of
1163 "Texture1D" -> Texture1D <$> obj .? "arg0" <*> obj .? "arg1"
1164 "Texture2D" -> Texture2D <$> obj .? "arg0" <*> obj .? "arg1"
1165 "Texture3D" -> Texture3D <$> obj .? "arg0"
1166 "TextureCube" -> TextureCube <$> obj .? "arg0"
1167 "TextureRect" -> TextureRect <$> obj .? "arg0"
1168 "Texture2DMS" -> Texture2DMS <$> obj .? "arg0" <*> obj .? "arg1" <*> obj .? "arg2" <*> obj .? "arg3"
1169 "TextureBuffer" -> TextureBuffer <$> obj .? "arg0"
1170
1171instance encodeJsonMipMap :: EncodeJson MipMap where
1172 encodeJson v = case v of
1173 Mip arg0 arg1 -> "tag" := "Mip" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1174 NoMip -> "tag" := "NoMip" ~> jsonEmptyObject
1175 AutoMip arg0 arg1 -> "tag" := "AutoMip" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1176
1177instance decodeJsonMipMap :: DecodeJson MipMap where
1178 decodeJson json = do
1179 obj <- decodeJson json
1180 tag <- obj .? "tag"
1181 case tag of
1182 "Mip" -> Mip <$> obj .? "arg0" <*> obj .? "arg1"
1183 "NoMip" -> pure NoMip
1184 "AutoMip" -> AutoMip <$> obj .? "arg0" <*> obj .? "arg1"
1185
1186instance encodeJsonFilter :: EncodeJson Filter where
1187 encodeJson v = case v of
1188 Nearest -> "tag" := "Nearest" ~> jsonEmptyObject
1189 Linear -> "tag" := "Linear" ~> jsonEmptyObject
1190 NearestMipmapNearest -> "tag" := "NearestMipmapNearest" ~> jsonEmptyObject
1191 NearestMipmapLinear -> "tag" := "NearestMipmapLinear" ~> jsonEmptyObject
1192 LinearMipmapNearest -> "tag" := "LinearMipmapNearest" ~> jsonEmptyObject
1193 LinearMipmapLinear -> "tag" := "LinearMipmapLinear" ~> jsonEmptyObject
1194
1195instance decodeJsonFilter :: DecodeJson Filter where
1196 decodeJson json = do
1197 obj <- decodeJson json
1198 tag <- obj .? "tag"
1199 case tag of
1200 "Nearest" -> pure Nearest
1201 "Linear" -> pure Linear
1202 "NearestMipmapNearest" -> pure NearestMipmapNearest
1203 "NearestMipmapLinear" -> pure NearestMipmapLinear
1204 "LinearMipmapNearest" -> pure LinearMipmapNearest
1205 "LinearMipmapLinear" -> pure LinearMipmapLinear
1206
1207instance encodeJsonEdgeMode :: EncodeJson EdgeMode where
1208 encodeJson v = case v of
1209 Repeat -> "tag" := "Repeat" ~> jsonEmptyObject
1210 MirroredRepeat -> "tag" := "MirroredRepeat" ~> jsonEmptyObject
1211 ClampToEdge -> "tag" := "ClampToEdge" ~> jsonEmptyObject
1212 ClampToBorder -> "tag" := "ClampToBorder" ~> jsonEmptyObject
1213
1214instance decodeJsonEdgeMode :: DecodeJson EdgeMode where
1215 decodeJson json = do
1216 obj <- decodeJson json
1217 tag <- obj .? "tag"
1218 case tag of
1219 "Repeat" -> pure Repeat
1220 "MirroredRepeat" -> pure MirroredRepeat
1221 "ClampToEdge" -> pure ClampToEdge
1222 "ClampToBorder" -> pure ClampToBorder
1223
1224instance encodeJsonImageSemantic :: EncodeJson ImageSemantic where
1225 encodeJson v = case v of
1226 Depth -> "tag" := "Depth" ~> jsonEmptyObject
1227 Stencil -> "tag" := "Stencil" ~> jsonEmptyObject
1228 Color -> "tag" := "Color" ~> jsonEmptyObject
1229
1230instance decodeJsonImageSemantic :: DecodeJson ImageSemantic where
1231 decodeJson json = do
1232 obj <- decodeJson json
1233 tag <- obj .? "tag"
1234 case tag of
1235 "Depth" -> pure Depth
1236 "Stencil" -> pure Stencil
1237 "Color" -> pure Color
1238
1239instance encodeJsonImageRef :: EncodeJson ImageRef where
1240 encodeJson v = case v of
1241 TextureImage arg0 arg1 arg2 -> "tag" := "TextureImage" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> "arg2" := arg2 ~> jsonEmptyObject
1242 Framebuffer arg0 -> "tag" := "Framebuffer" ~> "arg0" := arg0 ~> jsonEmptyObject
1243
1244instance decodeJsonImageRef :: DecodeJson ImageRef where
1245 decodeJson json = do
1246 obj <- decodeJson json
1247 tag <- obj .? "tag"
1248 case tag of
1249 "TextureImage" -> TextureImage <$> obj .? "arg0" <*> obj .? "arg1" <*> obj .? "arg2"
1250 "Framebuffer" -> Framebuffer <$> obj .? "arg0"
1251
1252instance encodeJsonClearImage :: EncodeJson ClearImage where
1253 encodeJson v = case v of
1254 ClearImage r ->
1255 "tag" := "ClearImage" ~>
1256 "imageSemantic" := r.imageSemantic ~>
1257 "clearValue" := r.clearValue ~>
1258 jsonEmptyObject
1259
1260instance decodeJsonClearImage :: DecodeJson ClearImage where
1261 decodeJson json = do
1262 obj <- decodeJson json
1263 tag <- obj .? "tag"
1264 case tag of
1265 "ClearImage" -> do
1266 imageSemantic <- obj .? "imageSemantic"
1267 clearValue <- obj .? "clearValue"
1268 pure $ ClearImage
1269 { imageSemantic:imageSemantic
1270 , clearValue:clearValue
1271 }
1272
1273instance encodeJsonCommand :: EncodeJson Command where
1274 encodeJson v = case v of
1275 SetRasterContext arg0 -> "tag" := "SetRasterContext" ~> "arg0" := arg0 ~> jsonEmptyObject
1276 SetAccumulationContext arg0 -> "tag" := "SetAccumulationContext" ~> "arg0" := arg0 ~> jsonEmptyObject
1277 SetRenderTarget arg0 -> "tag" := "SetRenderTarget" ~> "arg0" := arg0 ~> jsonEmptyObject
1278 SetProgram arg0 -> "tag" := "SetProgram" ~> "arg0" := arg0 ~> jsonEmptyObject
1279 SetSamplerUniform arg0 arg1 -> "tag" := "SetSamplerUniform" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1280 SetTexture arg0 arg1 -> "tag" := "SetTexture" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1281 SetSampler arg0 arg1 -> "tag" := "SetSampler" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1282 RenderSlot arg0 -> "tag" := "RenderSlot" ~> "arg0" := arg0 ~> jsonEmptyObject
1283 RenderStream arg0 -> "tag" := "RenderStream" ~> "arg0" := arg0 ~> jsonEmptyObject
1284 ClearRenderTarget arg0 -> "tag" := "ClearRenderTarget" ~> "arg0" := arg0 ~> jsonEmptyObject
1285 GenerateMipMap arg0 -> "tag" := "GenerateMipMap" ~> "arg0" := arg0 ~> jsonEmptyObject
1286 SaveImage arg0 arg1 -> "tag" := "SaveImage" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1287 LoadImage arg0 arg1 -> "tag" := "LoadImage" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
1288
1289instance decodeJsonCommand :: DecodeJson Command where
1290 decodeJson json = do
1291 obj <- decodeJson json
1292 tag <- obj .? "tag"
1293 case tag of
1294 "SetRasterContext" -> SetRasterContext <$> obj .? "arg0"
1295 "SetAccumulationContext" -> SetAccumulationContext <$> obj .? "arg0"
1296 "SetRenderTarget" -> SetRenderTarget <$> obj .? "arg0"
1297 "SetProgram" -> SetProgram <$> obj .? "arg0"
1298 "SetSamplerUniform" -> SetSamplerUniform <$> obj .? "arg0" <*> obj .? "arg1"
1299 "SetTexture" -> SetTexture <$> obj .? "arg0" <*> obj .? "arg1"
1300 "SetSampler" -> SetSampler <$> obj .? "arg0" <*> obj .? "arg1"
1301 "RenderSlot" -> RenderSlot <$> obj .? "arg0"
1302 "RenderStream" -> RenderStream <$> obj .? "arg0"
1303 "ClearRenderTarget" -> ClearRenderTarget <$> obj .? "arg0"
1304 "GenerateMipMap" -> GenerateMipMap <$> obj .? "arg0"
1305 "SaveImage" -> SaveImage <$> obj .? "arg0" <*> obj .? "arg1"
1306 "LoadImage" -> LoadImage <$> obj .? "arg0" <*> obj .? "arg1"
1307
1308instance encodeJsonSamplerDescriptor :: EncodeJson SamplerDescriptor where
1309 encodeJson v = case v of
1310 SamplerDescriptor r ->
1311 "tag" := "SamplerDescriptor" ~>
1312 "samplerWrapS" := r.samplerWrapS ~>
1313 "samplerWrapT" := r.samplerWrapT ~>
1314 "samplerWrapR" := r.samplerWrapR ~>
1315 "samplerMinFilter" := r.samplerMinFilter ~>
1316 "samplerMagFilter" := r.samplerMagFilter ~>
1317 "samplerBorderColor" := r.samplerBorderColor ~>
1318 "samplerMinLod" := r.samplerMinLod ~>
1319 "samplerMaxLod" := r.samplerMaxLod ~>
1320 "samplerLodBias" := r.samplerLodBias ~>
1321 "samplerCompareFunc" := r.samplerCompareFunc ~>
1322 jsonEmptyObject
1323
1324instance decodeJsonSamplerDescriptor :: DecodeJson SamplerDescriptor where
1325 decodeJson json = do
1326 obj <- decodeJson json
1327 tag <- obj .? "tag"
1328 case tag of
1329 "SamplerDescriptor" -> do
1330 samplerWrapS <- obj .? "samplerWrapS"
1331 samplerWrapT <- obj .? "samplerWrapT"
1332 samplerWrapR <- obj .? "samplerWrapR"
1333 samplerMinFilter <- obj .? "samplerMinFilter"
1334 samplerMagFilter <- obj .? "samplerMagFilter"
1335 samplerBorderColor <- obj .? "samplerBorderColor"
1336 samplerMinLod <- obj .? "samplerMinLod"
1337 samplerMaxLod <- obj .? "samplerMaxLod"
1338 samplerLodBias <- obj .? "samplerLodBias"
1339 samplerCompareFunc <- obj .? "samplerCompareFunc"
1340 pure $ SamplerDescriptor
1341 { samplerWrapS:samplerWrapS
1342 , samplerWrapT:samplerWrapT
1343 , samplerWrapR:samplerWrapR
1344 , samplerMinFilter:samplerMinFilter
1345 , samplerMagFilter:samplerMagFilter
1346 , samplerBorderColor:samplerBorderColor
1347 , samplerMinLod:samplerMinLod
1348 , samplerMaxLod:samplerMaxLod
1349 , samplerLodBias:samplerLodBias
1350 , samplerCompareFunc:samplerCompareFunc
1351 }
1352
1353instance encodeJsonTextureDescriptor :: EncodeJson TextureDescriptor where
1354 encodeJson v = case v of
1355 TextureDescriptor r ->
1356 "tag" := "TextureDescriptor" ~>
1357 "textureType" := r.textureType ~>
1358 "textureSize" := r.textureSize ~>
1359 "textureSemantic" := r.textureSemantic ~>
1360 "textureSampler" := r.textureSampler ~>
1361 "textureBaseLevel" := r.textureBaseLevel ~>
1362 "textureMaxLevel" := r.textureMaxLevel ~>
1363 jsonEmptyObject
1364
1365instance decodeJsonTextureDescriptor :: DecodeJson TextureDescriptor where
1366 decodeJson json = do
1367 obj <- decodeJson json
1368 tag <- obj .? "tag"
1369 case tag of
1370 "TextureDescriptor" -> do
1371 textureType <- obj .? "textureType"
1372 textureSize <- obj .? "textureSize"
1373 textureSemantic <- obj .? "textureSemantic"
1374 textureSampler <- obj .? "textureSampler"
1375 textureBaseLevel <- obj .? "textureBaseLevel"
1376 textureMaxLevel <- obj .? "textureMaxLevel"
1377 pure $ TextureDescriptor
1378 { textureType:textureType
1379 , textureSize:textureSize
1380 , textureSemantic:textureSemantic
1381 , textureSampler:textureSampler
1382 , textureBaseLevel:textureBaseLevel
1383 , textureMaxLevel:textureMaxLevel
1384 }
1385
1386instance encodeJsonParameter :: EncodeJson Parameter where
1387 encodeJson v = case v of
1388 Parameter r ->
1389 "tag" := "Parameter" ~>
1390 "name" := r.name ~>
1391 "ty" := r.ty ~>
1392 jsonEmptyObject
1393
1394instance decodeJsonParameter :: DecodeJson Parameter where
1395 decodeJson json = do
1396 obj <- decodeJson json
1397 tag <- obj .? "tag"
1398 case tag of
1399 "Parameter" -> do
1400 name <- obj .? "name"
1401 ty <- obj .? "ty"
1402 pure $ Parameter
1403 { name:name
1404 , ty:ty
1405 }
1406
1407instance encodeJsonProgram :: EncodeJson Program where
1408 encodeJson v = case v of
1409 Program r ->
1410 "tag" := "Program" ~>
1411 "programUniforms" := r.programUniforms ~>
1412 "programStreams" := r.programStreams ~>
1413 "programInTextures" := r.programInTextures ~>
1414 "programOutput" := r.programOutput ~>
1415 "vertexShader" := r.vertexShader ~>
1416 "geometryShader" := r.geometryShader ~>
1417 "fragmentShader" := r.fragmentShader ~>
1418 jsonEmptyObject
1419
1420instance decodeJsonProgram :: DecodeJson Program where
1421 decodeJson json = do
1422 obj <- decodeJson json
1423 tag <- obj .? "tag"
1424 case tag of
1425 "Program" -> do
1426 programUniforms <- obj .? "programUniforms"
1427 programStreams <- obj .? "programStreams"
1428 programInTextures <- obj .? "programInTextures"
1429 programOutput <- obj .? "programOutput"
1430 vertexShader <- obj .? "vertexShader"
1431 geometryShader <- obj .? "geometryShader"
1432 fragmentShader <- obj .? "fragmentShader"
1433 pure $ Program
1434 { programUniforms:programUniforms
1435 , programStreams:programStreams
1436 , programInTextures:programInTextures
1437 , programOutput:programOutput
1438 , vertexShader:vertexShader
1439 , geometryShader:geometryShader
1440 , fragmentShader:fragmentShader
1441 }
1442
1443instance encodeJsonSlot :: EncodeJson Slot where
1444 encodeJson v = case v of
1445 Slot r ->
1446 "tag" := "Slot" ~>
1447 "slotName" := r.slotName ~>
1448 "slotStreams" := r.slotStreams ~>
1449 "slotUniforms" := r.slotUniforms ~>
1450 "slotPrimitive" := r.slotPrimitive ~>
1451 "slotPrograms" := r.slotPrograms ~>
1452 jsonEmptyObject
1453
1454instance decodeJsonSlot :: DecodeJson Slot where
1455 decodeJson json = do
1456 obj <- decodeJson json
1457 tag <- obj .? "tag"
1458 case tag of
1459 "Slot" -> do
1460 slotName <- obj .? "slotName"
1461 slotStreams <- obj .? "slotStreams"
1462 slotUniforms <- obj .? "slotUniforms"
1463 slotPrimitive <- obj .? "slotPrimitive"
1464 slotPrograms <- obj .? "slotPrograms"
1465 pure $ Slot
1466 { slotName:slotName
1467 , slotStreams:slotStreams
1468 , slotUniforms:slotUniforms
1469 , slotPrimitive:slotPrimitive
1470 , slotPrograms:slotPrograms
1471 }
1472
1473instance encodeJsonStreamData :: EncodeJson StreamData where
1474 encodeJson v = case v of
1475 StreamData r ->
1476 "tag" := "StreamData" ~>
1477 "streamData" := r.streamData ~>
1478 "streamType" := r.streamType ~>
1479 "streamPrimitive" := r.streamPrimitive ~>
1480 "streamPrograms" := r.streamPrograms ~>
1481 jsonEmptyObject
1482
1483instance decodeJsonStreamData :: DecodeJson StreamData where
1484 decodeJson json = do
1485 obj <- decodeJson json
1486 tag <- obj .? "tag"
1487 case tag of
1488 "StreamData" -> do
1489 streamData <- obj .? "streamData"
1490 streamType <- obj .? "streamType"
1491 streamPrimitive <- obj .? "streamPrimitive"
1492 streamPrograms <- obj .? "streamPrograms"
1493 pure $ StreamData
1494 { streamData:streamData
1495 , streamType:streamType
1496 , streamPrimitive:streamPrimitive
1497 , streamPrograms:streamPrograms
1498 }
1499
1500instance encodeJsonTargetItem :: EncodeJson TargetItem where
1501 encodeJson v = case v of
1502 TargetItem r ->
1503 "tag" := "TargetItem" ~>
1504 "targetSemantic" := r.targetSemantic ~>
1505 "targetRef" := r.targetRef ~>
1506 jsonEmptyObject
1507
1508instance decodeJsonTargetItem :: DecodeJson TargetItem where
1509 decodeJson json = do
1510 obj <- decodeJson json
1511 tag <- obj .? "tag"
1512 case tag of
1513 "TargetItem" -> do
1514 targetSemantic <- obj .? "targetSemantic"
1515 targetRef <- obj .? "targetRef"
1516 pure $ TargetItem
1517 { targetSemantic:targetSemantic
1518 , targetRef:targetRef
1519 }
1520
1521instance encodeJsonRenderTarget :: EncodeJson RenderTarget where
1522 encodeJson v = case v of
1523 RenderTarget r ->
1524 "tag" := "RenderTarget" ~>
1525 "renderTargets" := r.renderTargets ~>
1526 jsonEmptyObject
1527
1528instance decodeJsonRenderTarget :: DecodeJson RenderTarget where
1529 decodeJson json = do
1530 obj <- decodeJson json
1531 tag <- obj .? "tag"
1532 case tag of
1533 "RenderTarget" -> do
1534 renderTargets <- obj .? "renderTargets"
1535 pure $ RenderTarget
1536 { renderTargets:renderTargets
1537 }
1538
1539instance encodeJsonBackend :: EncodeJson Backend where
1540 encodeJson v = case v of
1541 WebGL1 -> "tag" := "WebGL1" ~> jsonEmptyObject
1542 OpenGL33 -> "tag" := "OpenGL33" ~> jsonEmptyObject
1543
1544instance decodeJsonBackend :: DecodeJson Backend where
1545 decodeJson json = do
1546 obj <- decodeJson json
1547 tag <- obj .? "tag"
1548 case tag of
1549 "WebGL1" -> pure WebGL1
1550 "OpenGL33" -> pure OpenGL33
1551
1552instance encodeJsonPipeline :: EncodeJson Pipeline where
1553 encodeJson v = case v of
1554 Pipeline r ->
1555 "tag" := "Pipeline" ~>
1556 "backend" := r.backend ~>
1557 "textures" := r.textures ~>
1558 "samplers" := r.samplers ~>
1559 "targets" := r.targets ~>
1560 "programs" := r.programs ~>
1561 "slots" := r.slots ~>
1562 "streams" := r.streams ~>
1563 "commands" := r.commands ~>
1564 jsonEmptyObject
1565
1566instance decodeJsonPipeline :: DecodeJson Pipeline where
1567 decodeJson json = do
1568 obj <- decodeJson json
1569 tag <- obj .? "tag"
1570 case tag of
1571 "Pipeline" -> do
1572 backend <- obj .? "backend"
1573 textures <- obj .? "textures"
1574 samplers <- obj .? "samplers"
1575 targets <- obj .? "targets"
1576 programs <- obj .? "programs"
1577 slots <- obj .? "slots"
1578 streams <- obj .? "streams"
1579 commands <- obj .? "commands"
1580 pure $ Pipeline
1581 { backend:backend
1582 , textures:textures
1583 , samplers:samplers
1584 , targets:targets
1585 , programs:programs
1586 , slots:slots
1587 , streams:streams
1588 , commands:commands
1589 }
1590