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