summaryrefslogtreecommitdiff
path: root/ddl
diff options
context:
space:
mode:
authorCsaba Hruska <csaba.hruska@gmail.com>2015-12-21 13:48:22 +0100
committerCsaba Hruska <csaba.hruska@gmail.com>2015-12-21 13:48:22 +0100
commitbefc5afb22b36d744c403d103d591c5d190d394f (patch)
tree05e390bef55b0662a9a919b886322b66b113ff21 /ddl
parentdc8e31235fccbe5ea54d94b0ca69e005ca88c7ea (diff)
add lambdacube-ir haskell lib
Diffstat (limited to 'ddl')
-rw-r--r--ddl/Definitions.hs479
-rw-r--r--ddl/Generate.hs72
-rw-r--r--ddl/Language.hs393
-rw-r--r--ddl/lib/RT.cpp42
-rw-r--r--ddl/lib/RT.hpp188
-rw-r--r--ddl/lib/json.hpp7307
-rw-r--r--ddl/out/IR.cpp2864
-rw-r--r--ddl/out/IR.hpp1070
-rw-r--r--ddl/out/IR.hs1608
-rw-r--r--ddl/out/IR.purs1590
-rw-r--r--ddl/out/IR.swift1429
-rw-r--r--ddl/out/IR2.hpp1070
-rw-r--r--ddl/out/Mesh.cpp228
-rw-r--r--ddl/out/Mesh.hpp107
-rw-r--r--ddl/out/Mesh.hs114
-rw-r--r--ddl/out/Mesh.purs113
-rw-r--r--ddl/out/Mesh.swift174
-rw-r--r--ddl/out/Mesh2.hpp107
-rw-r--r--ddl/out/TypeInfo.cpp87
-rw-r--r--ddl/out/TypeInfo.hpp49
-rw-r--r--ddl/out/TypeInfo.hs79
-rw-r--r--ddl/out/TypeInfo.purs79
-rw-r--r--ddl/out/TypeInfo.swift134
-rw-r--r--ddl/out/TypeInfo2.hpp49
-rw-r--r--ddl/templates/data.cpp.ede41
-rw-r--r--ddl/templates/data.cs.ede27
-rw-r--r--ddl/templates/data.hpp.ede40
-rw-r--r--ddl/templates/data.hpp2.ede44
-rw-r--r--ddl/templates/data.hs.ede61
-rw-r--r--ddl/templates/data.java.ede26
-rw-r--r--ddl/templates/data.purs.ede68
-rw-r--r--ddl/templates/data.swift.ede141
-rw-r--r--ddl/test/idCpp.cpp31
-rw-r--r--ddl/test/idHs.hs8
34 files changed, 19919 insertions, 0 deletions
diff --git a/ddl/Definitions.hs b/ddl/Definitions.hs
new file mode 100644
index 0000000..9618407
--- /dev/null
+++ b/ddl/Definitions.hs
@@ -0,0 +1,479 @@
1{-# LANGUAGE OverloadedStrings #-}
2module Definitions (modules) where
3
4import Control.Monad.Writer
5import Language
6
7ir = do
8 -- type aliases
9 "StreamName" #= Int
10 "ProgramName" #= Int
11 "TextureName" #= Int
12 "SamplerName" #= Int
13 "UniformName" #= String
14 "SlotName" #= Int
15 "FrameBufferComponent" #= Int
16 "TextureUnit" #= Int
17 "RenderTargetName" #= Int
18 "TextureUnitMapping" #= Map "UniformName" "TextureUnit"
19
20 -- definitions
21 data_ "ArrayValue" $ do
22 const_ "VBoolArray" [Array Bool]
23 const_ "VIntArray" [Array Int32]
24 const_ "VWordArray" [Array Word32]
25 const_ "VFloatArray" [Array Float]
26
27 -- GPU type value reification, needed for shader codegen
28 data_ "Value" $ do
29 const_ "VBool" [Bool]
30 const_ "VV2B" [v2b]
31 const_ "VV3B" [v3b]
32 const_ "VV4B" [v4b]
33 const_ "VWord" [Word32]
34 const_ "VV2U" [v2u]
35 const_ "VV3U" [v3u]
36 const_ "VV4U" [v4u]
37 const_ "VInt" [Int32]
38 const_ "VV2I" [v2i]
39 const_ "VV3I" [v3i]
40 const_ "VV4I" [v4i]
41 const_ "VFloat" [Float]
42 const_ "VV2F" [v2f]
43 const_ "VV3F" [v3f]
44 const_ "VV4F" [v4f]
45 const_ "VM22F" [m22]
46 const_ "VM23F" [m23]
47 const_ "VM24F" [m24]
48 const_ "VM32F" [m32]
49 const_ "VM33F" [m33]
50 const_ "VM34F" [m34]
51 const_ "VM42F" [m42]
52 const_ "VM43F" [m43]
53 const_ "VM44F" [m44]
54
55 data_ "InputType" $ do
56 enum_ "Bool"
57 enum_ "V2B"
58 enum_ "V3B"
59 enum_ "V4B"
60 enum_ "Word"
61 enum_ "V2U"
62 enum_ "V3U"
63 enum_ "V4U"
64 enum_ "Int"
65 enum_ "V2I"
66 enum_ "V3I"
67 enum_ "V4I"
68 enum_ "Float"
69 enum_ "V2F"
70 enum_ "V3F"
71 enum_ "V4F"
72 enum_ "M22F"
73 enum_ "M23F"
74 enum_ "M24F"
75 enum_ "M32F"
76 enum_ "M33F"
77 enum_ "M34F"
78 enum_ "M42F"
79 enum_ "M43F"
80 enum_ "M44F"
81 -- shadow textures
82 enum_ "STexture1D"
83 enum_ "STexture2D"
84 enum_ "STextureCube"
85 enum_ "STexture1DArray"
86 enum_ "STexture2DArray"
87 enum_ "STexture2DRect"
88 -- float textures
89 enum_ "FTexture1D"
90 enum_ "FTexture2D"
91 enum_ "FTexture3D"
92 enum_ "FTextureCube"
93 enum_ "FTexture1DArray"
94 enum_ "FTexture2DArray"
95 enum_ "FTexture2DMS"
96 enum_ "FTexture2DMSArray"
97 enum_ "FTextureBuffer"
98 enum_ "FTexture2DRect"
99 -- int textures
100 enum_ "ITexture1D"
101 enum_ "ITexture2D"
102 enum_ "ITexture3D"
103 enum_ "ITextureCube"
104 enum_ "ITexture1DArray"
105 enum_ "ITexture2DArray"
106 enum_ "ITexture2DMS"
107 enum_ "ITexture2DMSArray"
108 enum_ "ITextureBuffer"
109 enum_ "ITexture2DRect"
110 -- uint textures
111 enum_ "UTexture1D"
112 enum_ "UTexture2D"
113 enum_ "UTexture3D"
114 enum_ "UTextureCube"
115 enum_ "UTexture1DArray"
116 enum_ "UTexture2DArray"
117 enum_ "UTexture2DMS"
118 enum_ "UTexture2DMSArray"
119 enum_ "UTextureBuffer"
120 enum_ "UTexture2DRect"
121 deriving_ [Haskell] [Eq,Ord]
122
123 data_ "PointSpriteCoordOrigin" $ do
124 enum_ "LowerLeft"
125 enum_ "UpperLeft"
126
127 data_ "PointSize" $ do
128 const_ "PointSize" [Float]
129 enum_ "ProgramPointSize"
130
131 data_ "PolygonOffset" $ do
132 enum_ "NoOffset"
133 const_ "Offset" [Float,Float]
134
135 data_ "FrontFace" $ do
136 enum_ "CCW"
137 enum_ "CW"
138
139 data_ "PolygonMode" $ do
140 const_ "PolygonPoint" ["PointSize"]
141 const_ "PolygonLine" [Float]
142 enum_ "PolygonFill"
143
144 data_ "ProvokingVertex" $ do
145 enum_ "FirstVertex"
146 enum_ "LastVertex"
147
148 data_ "CullMode" $ do
149 enum_ "CullNone"
150 const_ "CullFront" ["FrontFace"]
151 const_ "CullBack" ["FrontFace"]
152
153 data_ "ComparisonFunction" $ do
154 enum_ "Never"
155 enum_ "Less"
156 enum_ "Equal"
157 enum_ "Lequal"
158 enum_ "Greater"
159 enum_ "Notequal"
160 enum_ "Gequal"
161 enum_ "Always"
162
163 "DepthFunction" #= "ComparisonFunction"
164
165 data_ "StencilOperation" $ do
166 enum_ "OpZero"
167 enum_ "OpKeep"
168 enum_ "OpReplace"
169 enum_ "OpIncr"
170 enum_ "OpIncrWrap"
171 enum_ "OpDecr"
172 enum_ "OpDecrWrap"
173 enum_ "OpInvert"
174
175 data_ "BlendEquation" $ do
176 enum_ "FuncAdd"
177 enum_ "FuncSubtract"
178 enum_ "FuncReverseSubtract"
179 enum_ "Min"
180 enum_ "Max"
181
182 data_ "BlendingFactor" $ do
183 enum_ "Zero"
184 enum_ "One"
185 enum_ "SrcColor"
186 enum_ "OneMinusSrcColor"
187 enum_ "DstColor"
188 enum_ "OneMinusDstColor"
189 enum_ "SrcAlpha"
190 enum_ "OneMinusSrcAlpha"
191 enum_ "DstAlpha"
192 enum_ "OneMinusDstAlpha"
193 enum_ "ConstantColor"
194 enum_ "OneMinusConstantColor"
195 enum_ "ConstantAlpha"
196 enum_ "OneMinusConstantAlpha"
197 enum_ "SrcAlphaSaturate"
198
199 data_ "LogicOperation" $ do
200 enum_ "Clear"
201 enum_ "And"
202 enum_ "AndReverse"
203 enum_ "Copy"
204 enum_ "AndInverted"
205 enum_ "Noop"
206 enum_ "Xor"
207 enum_ "Or"
208 enum_ "Nor"
209 enum_ "Equiv"
210 enum_ "Invert"
211 enum_ "OrReverse"
212 enum_ "CopyInverted"
213 enum_ "OrInverted"
214 enum_ "Nand"
215 enum_ "Set"
216
217 data_ "StencilOps" $ do
218 constR_ "StencilOps"
219 [ "frontStencilOp" #:: "StencilOperation" -- Used for front faced triangles and other primitives.
220 , "backStencilOp" #:: "StencilOperation" -- Used for back faced triangles.
221 ]
222
223 data_ "StencilTest" $ do
224 constR_ "StencilTest"
225 [ "stencilComparision" #:: "ComparisonFunction" -- The function used to compare the @stencilReference@ and the stencil buffers value with.
226 , "stencilReference" #:: Int32 -- The value to compare with the stencil buffer's value.
227 , "stencilMask" #:: Word32 -- A bit mask with ones in each position that should be compared and written to the stencil buffer.
228 ]
229
230 data_ "StencilTests" $ do
231 const_ "StencilTests" ["StencilTest", "StencilTest"]
232
233 -- primitive types
234 data_ "FetchPrimitive" $ do
235 enum_ "Points"
236 enum_ "Lines"
237 enum_ "Triangles"
238 enum_ "LinesAdjacency"
239 enum_ "TrianglesAdjacency"
240 deriving_ [PureScript] [Show,Eq]
241
242 data_ "OutputPrimitive" $ do
243 enum_ "TrianglesOutput"
244 enum_ "LinesOutput"
245 enum_ "PointsOutput"
246
247 data_ "ColorArity" $ do
248 enum_ "Red"
249 enum_ "RG"
250 enum_ "RGB"
251 enum_ "RGBA"
252 deriving_ [PureScript] [Show]
253
254 data_ "Blending" $ do
255 enum_ "NoBlending"
256 const_ "BlendLogicOp" ["LogicOperation"]
257 constR_ "Blend"
258 [ "colorEqSrc" #:: "BlendEquation"
259 , "alphaEqSrc" #:: "BlendEquation"
260 , "colorFSrc" #:: "BlendingFactor"
261 , "colorFDst" #:: "BlendingFactor"
262 , "alphaFSrc" #:: "BlendingFactor"
263 , "alphaFDst" #:: "BlendingFactor"
264 , "color" #:: v4f
265 ]
266
267 data_ "RasterContext" $ do
268 const_ "PointCtx" ["PointSize", Float, "PointSpriteCoordOrigin"]
269 const_ "LineCtx" [Float, "ProvokingVertex"]
270 const_ "TriangleCtx" ["CullMode", "PolygonMode", "PolygonOffset", "ProvokingVertex"]
271
272 data_ "FragmentOperation" $ do
273 const_ "DepthOp" ["DepthFunction", Bool]
274 const_ "StencilOp" ["StencilTests", "StencilOps", "StencilOps"]
275 const_ "ColorOp" ["Blending", "Value"]
276
277 data_ "AccumulationContext" $ do
278 constR_ "AccumulationContext"
279 [ "accViewportName" #:: Maybe String
280 , "accOperations" #:: List "FragmentOperation"
281 ]
282
283 data_ "TextureDataType" $ do
284 const_ "FloatT" ["ColorArity"]
285 const_ "IntT" ["ColorArity"]
286 const_ "WordT" ["ColorArity"]
287 enum_ "ShadowT"
288 deriving_ [PureScript] [Show]
289
290 data_ "TextureType" $ do
291 const_ "Texture1D" ["TextureDataType", Int]
292 const_ "Texture2D" ["TextureDataType", Int]
293 const_ "Texture3D" ["TextureDataType"]
294 const_ "TextureCube" ["TextureDataType"]
295 const_ "TextureRect" ["TextureDataType"]
296 const_ "Texture2DMS" ["TextureDataType", Int, Int, Bool]
297 const_ "TextureBuffer" ["TextureDataType"]
298
299 data_ "MipMap" $ do
300 const_ "Mip" [Int,Int] -- Base level, Max level
301 enum_ "NoMip"
302 const_ "AutoMip" [Int,Int] -- Base level, Max level
303
304 data_ "Filter" $ do
305 enum_ "Nearest"
306 enum_ "Linear"
307 enum_ "NearestMipmapNearest"
308 enum_ "NearestMipmapLinear"
309 enum_ "LinearMipmapNearest"
310 enum_ "LinearMipmapLinear"
311
312 data_ "EdgeMode" $ do
313 enum_ "Repeat"
314 enum_ "MirroredRepeat"
315 enum_ "ClampToEdge"
316 enum_ "ClampToBorder"
317
318 data_ "ImageSemantic" $ do
319 enum_ "Depth"
320 enum_ "Stencil"
321 enum_ "Color"
322 deriving_ [Haskell] [Eq]
323
324 data_ "ImageRef" $ do
325 const_ "TextureImage" ["TextureName", Int, Maybe Int] -- Texture name, mip index, array index
326 const_ "Framebuffer" ["ImageSemantic"]
327
328 data_ "ClearImage" $ do
329 constR_ "ClearImage"
330 [ "imageSemantic" #:: "ImageSemantic"
331 , "clearValue" #:: "Value"
332 ]
333
334 data_ "Command" $ do
335 const_ "SetRasterContext" ["RasterContext"]
336 const_ "SetAccumulationContext" ["AccumulationContext"]
337 const_ "SetRenderTarget" ["RenderTargetName"]
338 const_ "SetProgram" ["ProgramName"] --TextureUnitMapping -- adding texture unit map to set program command seems to be better solution than the current one
339 const_ "SetSamplerUniform" ["UniformName", "TextureUnit"] -- hint: currently the texture unit mapping is encoded with this command
340 const_ "SetTexture" ["TextureUnit", "TextureName"] -- binds texture to the specified texture unit
341 const_ "SetSampler" ["TextureUnit", Maybe "SamplerName"] -- binds sampler to the specified texture unit
342 const_ "RenderSlot" ["SlotName"]
343 const_ "RenderStream" ["StreamName"]
344 const_ "ClearRenderTarget" [Array "ClearImage"]
345 const_ "GenerateMipMap" ["TextureUnit"]
346 const_ "SaveImage" ["FrameBufferComponent", "ImageRef"] -- from framebuffer component to texture (image)
347 const_ "LoadImage" ["ImageRef", "FrameBufferComponent"] -- from texture (image) to framebuffer component
348
349 data_ "SamplerDescriptor" $ do
350 constR_ "SamplerDescriptor"
351 [ "samplerWrapS" #:: "EdgeMode"
352 , "samplerWrapT" #:: Maybe "EdgeMode"
353 , "samplerWrapR" #:: Maybe "EdgeMode"
354 , "samplerMinFilter" #:: "Filter"
355 , "samplerMagFilter" #:: "Filter"
356 , "samplerBorderColor" #:: "Value"
357 , "samplerMinLod" #:: Maybe Float
358 , "samplerMaxLod" #:: Maybe Float
359 , "samplerLodBias" #:: Float
360 , "samplerCompareFunc" #:: Maybe "ComparisonFunction"
361 ]
362
363 data_ "TextureDescriptor" $ do -- texture size, type, array, mipmap
364 constR_ "TextureDescriptor"
365 [ "textureType" #:: "TextureType"
366 , "textureSize" #:: "Value"
367 , "textureSemantic" #:: "ImageSemantic"
368 , "textureSampler" #:: "SamplerDescriptor"
369 , "textureBaseLevel" #:: Int
370 , "textureMaxLevel" #:: Int
371 ]
372
373 data_ "Parameter" $ do
374 constR_ "Parameter"
375 [ "name" #:: String
376 , "ty" #:: "InputType"
377 ]
378
379 data_ "Program" $ do -- AST, input
380 constR_ "Program"
381 [ "programUniforms" #:: Map "UniformName" "InputType" -- uniform input (value based uniforms only / no textures)
382 , "programStreams" #:: Map "UniformName" "Parameter" -- vertex shader input attribute name -> (slot attribute name, attribute type)
383 , "programInTextures" #:: Map "UniformName" "InputType" -- all textures (uniform textures and render textures) referenced by the program
384 , "programOutput" #:: Array "Parameter"
385 , "vertexShader" #:: String
386 , "geometryShader" #:: Maybe String
387 , "fragmentShader" #:: String
388 ]
389
390 data_ "Slot" $ do -- input, primitive type
391 constR_ "Slot"
392 [ "slotName" #:: String
393 , "slotStreams" #:: Map String "InputType"
394 , "slotUniforms" #:: Map "UniformName" "InputType"
395 , "slotPrimitive" #:: "FetchPrimitive"
396 , "slotPrograms" #:: Array "ProgramName"
397 ]
398
399 data_ "StreamData" $ do
400 constR_ "StreamData"
401 [ "streamData" #:: Map String "ArrayValue"
402 , "streamType" #:: Map String "InputType"
403 , "streamPrimitive" #:: "FetchPrimitive"
404 , "streamPrograms" #:: Array "ProgramName"
405 ]
406
407 data_ "TargetItem" $ do
408 constR_ "TargetItem"
409 [ "targetSemantic" #:: "ImageSemantic"
410 , "targetRef" #:: Maybe "ImageRef"
411 ]
412
413 data_ "RenderTarget" $ do
414 constR_ "RenderTarget"
415 [ "renderTargets" #:: Array "TargetItem" -- render texture or default framebuffer (semantic, render texture for the program output)
416 ]
417
418 data_ "Backend" $ do
419 enum_ "WebGL1"
420 enum_ "OpenGL33"
421
422 data_ "Pipeline" $ do
423 constR_ "Pipeline"
424 [ "backend" #:: "Backend"
425 , "textures" #:: Array "TextureDescriptor"
426 , "samplers" #:: Array "SamplerDescriptor"
427 , "targets" #:: Array "RenderTarget"
428 , "programs" #:: Array "Program"
429 , "slots" #:: Array "Slot"
430 , "streams" #:: Array "StreamData"
431 , "commands" #:: Array "Command"
432 ]
433 deriving_ [Haskell] [Show]
434
435mesh = do
436 data_ "MeshAttribute" $ do
437 const_ "A_Float" [Array Float]
438 const_ "A_V2F" [Array v2f]
439 const_ "A_V3F" [Array v3f]
440 const_ "A_V4F" [Array v4f]
441 const_ "A_M22F" [Array m22]
442 const_ "A_M33F" [Array m33]
443 const_ "A_M44F" [Array m44]
444 const_ "A_Int" [Array Int32]
445 const_ "A_Word" [Array Word32]
446
447 data_ "MeshPrimitive" $ do
448 enum_ "P_Points"
449 enum_ "P_TriangleStrip"
450 enum_ "P_Triangles"
451 const_ "P_TriangleStripI" [Array Int32]
452 const_ "P_TrianglesI" [Array Int32]
453
454 data_ "Mesh" $ do
455 constR_ "Mesh"
456 [ "mAttributes" #:: Map String "MeshAttribute"
457 , "mPrimitive" #:: "MeshPrimitive"
458 ]
459
460typeInfo = do
461 data_ "TypeInfo" $ do
462 constR_ "TypeInfo"
463 [ "startLine" #:: Int
464 , "startColumn" #:: Int
465 , "endLine" #:: Int
466 , "endColumn" #:: Int
467 , "text" #:: String
468 ]
469
470 data_ "MyEither" $ do
471 const_ "MyLeft" ["TypeInfo", Array "TypeInfo"]
472 const_ "MyRight" ["Pipeline", Array "TypeInfo"]
473
474modules = do
475 module_ "IR" ir
476 module_ "Mesh" mesh
477 module_ "TypeInfo" $ do
478 import_ ["IR"]
479 typeInfo
diff --git a/ddl/Generate.hs b/ddl/Generate.hs
new file mode 100644
index 0000000..5f5c0d0
--- /dev/null
+++ b/ddl/Generate.hs
@@ -0,0 +1,72 @@
1{-# LANGUAGE OverloadedStrings, FlexibleInstances #-}
2import qualified Data.Text.Lazy as LText
3import Text.EDE
4import Text.EDE.Filters
5
6import Data.HashMap.Strict (HashMap)
7import qualified Data.HashMap.Strict as HashMap
8import Data.Text (Text)
9import qualified Data.Map as Map
10
11import Data.Time.Clock
12import Control.Monad.Writer
13
14import Definitions
15import Language
16
17instance Unquote [Field]
18instance Unquote [Char]
19instance Quote [Char]
20instance Unquote DataDef
21instance Unquote Type
22
23main :: IO ()
24main = do
25 dataSwift <- eitherParseFile "templates/data.swift.ede"
26 dataJava <- eitherParseFile "templates/data.java.ede"
27 dataHpp <- eitherParseFile "templates/data.hpp.ede"
28 dataHpp2 <- eitherParseFile "templates/data.hpp2.ede"
29 dataCpp <- eitherParseFile "templates/data.cpp.ede"
30 dataCs <- eitherParseFile "templates/data.cs.ede"
31 dataHs <- eitherParseFile "templates/data.hs.ede"
32 dataPs <- eitherParseFile "templates/data.purs.ede"
33 let generate (ModuleDef name imports def) = do
34 dt <- getCurrentTime
35 let env = fromPairs
36 [ "dataAndType" .= def
37 , "definitions" .= [a | a@DataDef{} <- def ]
38 , "moduleName" .= name
39 , "dateTime" .= dt
40 , "imports" .= imports
41 ]
42 aliasMap = Map.fromList [(n,t) | TypeAlias n t <- def]
43 mylib :: HashMap Text Term
44 mylib = HashMap.fromList
45 [ "hasFieldNames" @: hasFieldNames
46 , "parens" @: parens
47 , "constType" @: constType
48 , "hsType" @: hsType aliasMap
49 , "psType" @: psType aliasMap
50 , "cppType" @: cppType aliasMap
51 , "csType" @: csType aliasMap
52 , "javaType" @: javaType aliasMap
53 , "swiftType" @: swiftType aliasMap
54 ]
55
56 -- Haskell
57 either error (\x -> writeFile ("out/" ++ name ++ ".hs") $ LText.unpack x) $ dataHs >>= (\t -> eitherRenderWith mylib t env)
58 -- Purescript
59 either error (\x -> writeFile ("out/" ++ name ++ ".purs") $ LText.unpack x) $ dataPs >>= (\t -> eitherRenderWith mylib t env)
60 -- C++
61 either error (\x -> writeFile ("out/" ++ name ++ "2.hpp") $ LText.unpack x) $ dataHpp2 >>= (\t -> eitherRenderWith mylib t env)
62 either error (\x -> writeFile ("out/" ++ name ++ ".hpp") $ LText.unpack x) $ dataHpp >>= (\t -> eitherRenderWith mylib t env)
63 either error (\x -> writeFile ("out/" ++ name ++ ".cpp") $ LText.unpack x) $ dataCpp >>= (\t -> eitherRenderWith mylib t env)
64 {-
65 -- Java
66 either error (\x -> writeFile ("out/" ++ name ++ ".java") $ LText.unpack x) $ dataJava >>= (\t -> eitherRenderWith mylib t env)
67 -- C#
68 either error (\x -> writeFile ("out/" ++ name ++ ".cs") $ LText.unpack x) $ dataCs >>= (\t -> eitherRenderWith mylib t env)
69 -}
70 -- Swift
71 either error (\x -> writeFile ("out/" ++ name ++ ".swift") $ LText.unpack x) $ dataSwift >>= (\t -> eitherRenderWith mylib t env)
72 mapM_ generate $ execWriter modules
diff --git a/ddl/Language.hs b/ddl/Language.hs
new file mode 100644
index 0000000..79c3056
--- /dev/null
+++ b/ddl/Language.hs
@@ -0,0 +1,393 @@
1{-# LANGUAGE RankNTypes, OverloadedStrings, DeriveGeneric, LambdaCase #-}
2module Language where
3
4import GHC.Generics
5import Data.Aeson (ToJSON(..),FromJSON(..))
6import Control.Monad.Writer
7import Data.String
8import Data.List
9import Data.Map (Map)
10import qualified Data.Map as Map
11
12instance IsString Type where
13 fromString a = Data a
14
15data ModuleDef
16 = ModuleDef
17 { moduleName :: String
18 , imports :: [String]
19 , definitions :: [DataDef]
20 }
21 deriving (Show,Generic)
22
23data DataDef
24 = DataDef
25 { dataName :: String
26 , constructors :: [ConstructorDef]
27 , instances :: [Instance]
28 }
29 | TypeAlias
30 { aliasName :: String
31 , aliasType :: Type
32 }
33 deriving (Show,Generic)
34
35data ConstructorDef
36 = ConstructorDef
37 { name :: String
38 , fields :: [Field]
39 }
40 deriving (Show,Generic)
41
42data Field
43 = Field
44 { fieldName :: String
45 , fieldType :: Type
46 }
47 deriving (Show,Generic)
48
49data Instance
50 = Show
51 | Eq
52 | Ord
53 deriving (Show,Generic)
54
55data Target
56 = Haskell
57 | PureScript
58 | Cpp
59 | CSharp
60 deriving (Show,Generic)
61
62data Type
63 = Int
64 | Int32
65 | Word
66 | Word32
67 | Float
68 | Bool
69 | String
70 | V2 Type
71 | V3 Type
72 | V4 Type
73 -- higher order types
74 | Array Type
75 | List Type
76 | Maybe Type
77 | Map Type Type
78 -- user defined
79 | Data String
80 deriving (Show,Generic)
81
82parens :: String -> String
83parens a
84 | 1 == length (words a) = a
85 | otherwise = "(" ++ a ++ ")"
86
87type AliasMap = Map String Type
88
89normalize :: AliasMap -> Type -> Type
90normalize aliasMap t@(Data n) = Map.findWithDefault t n aliasMap
91normalize _ t = t
92
93psType :: AliasMap -> Type -> String
94psType aliasMap = \case
95 Int -> "Int"
96 Int32 -> "Int32"
97 Word -> "Word"
98 Word32 -> "Word32"
99 Float -> "Float"
100 Bool -> "Bool"
101 String -> "String"
102
103 V2 Int -> "V2I"
104 V2 Word -> "V2U"
105 V2 Float -> "V2F"
106 V2 Bool -> "V2B"
107 V2 (V2 Float) -> "M22F"
108 V2 (V3 Float) -> "M32F"
109 V2 (V4 Float) -> "M42F"
110
111 V3 Int -> "V3I"
112 V3 Word -> "V3U"
113 V3 Float -> "V3F"
114 V3 Bool -> "V3B"
115 V3 (V2 Float) -> "M23F"
116 V3 (V3 Float) -> "M33F"
117 V3 (V4 Float) -> "M43F"
118
119 V4 Int -> "V4I"
120 V4 Word -> "V4U"
121 V4 Float -> "V4F"
122 V4 Bool -> "V4B"
123 V4 (V2 Float) -> "M24F"
124 V4 (V3 Float) -> "M34F"
125 V4 (V4 Float) -> "M44F"
126
127 Array t -> "Array " ++ parens (psType aliasMap t)
128 List t -> "List " ++ parens (psType aliasMap t)
129 Maybe t -> "Maybe " ++ parens (psType aliasMap t)
130 Map k v
131 | String <- normalize aliasMap k -> "StrMap " ++ parens (psType aliasMap v)
132 | otherwise -> "Map " ++ parens (psType aliasMap k) ++ " " ++ parens (psType aliasMap v)
133 -- user defined
134 Data t -> t
135 x -> error $ "unknown type: " ++ show x
136
137hsType :: AliasMap -> Type -> String
138hsType aliasMap = \case
139 Int -> "Int"
140 Int32 -> "Int32"
141 Word -> "Word"
142 Word32 -> "Word32"
143 Float -> "Float"
144 Bool -> "Bool"
145 String -> "String"
146
147 V2 Int -> "V2I"
148 V2 Word -> "V2U"
149 V2 Float -> "V2F"
150 V2 Bool -> "V2B"
151 V2 (V2 Float) -> "M22F"
152 V2 (V3 Float) -> "M32F"
153 V2 (V4 Float) -> "M42F"
154
155 V3 Int -> "V3I"
156 V3 Word -> "V3U"
157 V3 Float -> "V3F"
158 V3 Bool -> "V3B"
159 V3 (V2 Float) -> "M23F"
160 V3 (V3 Float) -> "M33F"
161 V3 (V4 Float) -> "M43F"
162
163 V4 Int -> "V4I"
164 V4 Word -> "V4U"
165 V4 Float -> "V4F"
166 V4 Bool -> "V4B"
167 V4 (V2 Float) -> "M24F"
168 V4 (V3 Float) -> "M34F"
169 V4 (V4 Float) -> "M44F"
170
171 Array t -> "Vector " ++ parens (hsType aliasMap t)
172 List t -> "[" ++ hsType aliasMap t ++ "]"
173 Maybe t -> "Maybe " ++ parens (hsType aliasMap t)
174 Map k v -> "Map " ++ parens (hsType aliasMap k) ++ " " ++ parens (hsType aliasMap v)
175 -- user defined
176 Data t -> t
177 x -> error $ "unknown type: " ++ show x
178
179swiftType :: AliasMap -> Type -> String
180swiftType aliasMap = \case
181 Int -> "Int"
182 Int32 -> "Int32"
183 Word -> "UInt"
184 Word32 -> "UInt32"
185 Float -> "Float"
186 Bool -> "Bool"
187 String -> "String"
188{-
189 V2 Int -> "V2I"
190 V2 Word -> "V2U"
191 V2 Float -> "V2F"
192 V2 Bool -> "V2B"
193 V2 (V2 Float) -> "M22F"
194 V2 (V3 Float) -> "M32F"
195 V2 (V4 Float) -> "M42F"
196
197 V3 Int -> "V3I"
198 V3 Word -> "V3U"
199 V3 Float -> "V3F"
200 V3 Bool -> "V3B"
201 V3 (V2 Float) -> "M23F"
202 V3 (V3 Float) -> "M33F"
203 V3 (V4 Float) -> "M43F"
204
205 V4 Int -> "V4I"
206 V4 Word -> "V4U"
207 V4 Float -> "V4F"
208 V4 Bool -> "V4B"
209 V4 (V2 Float) -> "M24F"
210 V4 (V3 Float) -> "M34F"
211 V4 (V4 Float) -> "M44F"
212-}
213 Array t -> "Array<" ++ swiftType aliasMap t ++ ">"
214 List t -> "Array<" ++ swiftType aliasMap t ++ ">"
215 Maybe t -> "Maybe<" ++ swiftType aliasMap t ++ ">"
216 Map k v -> "Dictionary<" ++ swiftType aliasMap k ++ ", " ++ swiftType aliasMap v ++ ">"
217 -- user defined
218 Data t -> t
219 _ -> "Int"
220 x -> error $ "unknown type: " ++ show x
221
222javaType :: AliasMap -> Type -> String -- TODO
223javaType aliasMap a = case normalize aliasMap a of
224 Data t -> t
225 Int -> "int"
226 Int32 -> "int"
227 Word -> "int"
228 Word32 -> "int"
229 Float -> "float"
230 Bool -> "boolean"
231 String -> "String"
232 Array t -> "ArrayList<" ++ javaType aliasMap t ++ ">"
233 List t -> "ArrayList<" ++ javaType aliasMap t ++ ">"
234 Map k v -> "HashMap<" ++ javaType aliasMap k ++ ", " ++ javaType aliasMap v ++ ">"
235 _ -> "int"
236
237csType :: AliasMap -> Type -> String -- TODO
238csType aliasMap a = case normalize aliasMap a of
239 Data t -> t
240 Int -> "int"
241 Int32 -> "int"
242 Word -> "uint"
243 Word32 -> "uint"
244 Float -> "float"
245 Bool -> "bool"
246 String -> "string"
247 Array t -> "List<" ++ csType aliasMap t ++ ">"
248 List t -> "List<" ++ csType aliasMap t ++ ">"
249 Map k v -> "Dictionary<" ++ csType aliasMap k ++ ", " ++ csType aliasMap v ++ ">"
250 _ -> "int"
251
252cppType :: AliasMap -> Type -> String
253cppType aliasMap = \case
254 Int -> "Int"
255 Int32 -> "Int32"
256 Word -> "Word"
257 Word32 -> "Word32"
258 Float -> "Float"
259 Bool -> "Bool"
260 String -> "String"
261
262 V2 Int -> "V2I"
263 V2 Word -> "V2U"
264 V2 Float -> "V2F"
265 V2 Bool -> "V2B"
266 V2 (V2 Float) -> "M22F"
267 V2 (V3 Float) -> "M32F"
268 V2 (V4 Float) -> "M42F"
269
270 V3 Int -> "V3I"
271 V3 Word -> "V3U"
272 V3 Float -> "V3F"
273 V3 Bool -> "V3B"
274 V3 (V2 Float) -> "M23F"
275 V3 (V3 Float) -> "M33F"
276 V3 (V4 Float) -> "M43F"
277
278 V4 Int -> "V4I"
279 V4 Word -> "V4U"
280 V4 Float -> "V4F"
281 V4 Bool -> "V4B"
282 V4 (V2 Float) -> "M24F"
283 V4 (V3 Float) -> "M34F"
284 V4 (V4 Float) -> "M44F"
285
286 Array t -> "std::vector<" ++ cppType aliasMap t ++ ">"
287 List t -> "std::vector<" ++ cppType aliasMap t ++ ">"
288 Maybe t -> "Maybe<" ++ cppType aliasMap t ++ ">"
289 Map k v -> "std::map<" ++ cppType aliasMap k ++ ", " ++ cppType aliasMap v ++ ">"
290 -- user defined
291 Data t -> case normalize aliasMap (Data t) of
292 Data _ -> "std::shared_ptr<::" ++ t ++ ">"
293 _ -> "::" ++ t
294 x -> error $ "unknown type: " ++ show x
295
296hasFieldNames :: [Field] -> Bool
297hasFieldNames [] = False
298hasFieldNames l = all (not . null . fieldName) l
299
300constType :: DataDef -> String
301constType = head . words . show
302
303instance ToJSON ConstructorDef
304instance ToJSON DataDef
305instance ToJSON Instance
306instance ToJSON Field
307instance ToJSON Type
308
309instance FromJSON ConstructorDef
310instance FromJSON DataDef
311instance FromJSON Instance
312instance FromJSON Field
313instance FromJSON Type
314
315type MDef = Writer [ModuleDef]
316type DDef = Writer ([DataDef],[String])
317type CDef = Writer ([ConstructorDef],[Instance])
318
319module_ :: String -> DDef () -> MDef ()
320module_ n m = tell [let (d,i) = execWriter m in ModuleDef n i d]
321
322import_ :: [String] -> DDef ()
323import_ l = tell (mempty,l)
324
325data_ :: String -> CDef () -> DDef ()
326data_ n l = tell ([let (c,i) = execWriter l in DataDef n c i],mempty)
327
328alias_ :: String -> Type -> DDef ()
329alias_ n t = tell ([TypeAlias n t],mempty)
330
331a #= b = alias_ a b
332
333class IsField a where
334 toField :: a -> Field
335
336instance IsField Field where
337 toField a = a
338
339instance IsField Type where
340 toField a = Field "" a
341
342deriving_ :: [Target] -> [Instance] -> CDef ()
343deriving_ t l = tell (mempty,l)
344
345const_ :: String -> [Type] -> CDef ()
346const_ n t = tell ([ConstructorDef n [Field a b | Field a b <- map toField t]],mempty)
347
348constR_ :: String -> [Field] -> CDef ()
349constR_ n t = tell ([ConstructorDef n [Field a b | Field a b <- map toField t]],mempty)
350
351enum_ :: String -> CDef ()
352enum_ n = tell ([ConstructorDef n []],mempty)
353
354v2b = V2 Bool
355v3b = V3 Bool
356v4b = V4 Bool
357v2u = V2 Word
358v3u = V3 Word
359v4u = V4 Word
360v2i = V2 Int
361v3i = V3 Int
362v4i = V4 Int
363v2f = V2 Float
364v3f = V3 Float
365v4f = V4 Float
366m22 = V2 v2f
367m23 = V3 v2f
368m24 = V4 v2f
369m32 = V2 v3f
370m33 = V3 v3f
371m34 = V4 v3f
372m42 = V2 v4f
373m43 = V3 v4f
374m44 = V4 v4f
375
376(#::) :: String -> Type -> Field
377a #:: b = Field a b
378
379{-
380 definitions:
381 ADT
382 Record
383 Vector
384
385 instances:
386 Show
387 Eq
388 Ord
389
390 serialization:
391 json: encode/decode
392 other?
393-} \ No newline at end of file
diff --git a/ddl/lib/RT.cpp b/ddl/lib/RT.cpp
new file mode 100644
index 0000000..97701b2
--- /dev/null
+++ b/ddl/lib/RT.cpp
@@ -0,0 +1,42 @@
1#include "RT.hpp"
2
3template<> json toJSON<String>(String &v) {
4 return json(v);
5}
6
7template<> json toJSON<Float>(Float &v) {
8 return json(v);
9}
10
11template<> json toJSON<bool>(bool &v) {
12 return json(v);
13}
14
15template<> json toJSON<int>(int &v) {
16 return json(v);
17}
18
19template<> json toJSON<unsigned int>(unsigned int &v) {
20 return json(v);
21}
22
23template<> String fromJSON<String>(W<String> v, json &obj) {
24 return obj.get<String>();
25}
26
27template<> Float fromJSON<Float>(W<Float> v, json &obj) {
28 return obj.get<Float>();
29}
30
31template<> bool fromJSON<bool>(W<bool> v, json &obj) {
32 return obj.get<bool>();
33}
34
35template<> int fromJSON<int>(W<int> v, json &obj) {
36 return obj.get<int>();
37}
38
39template<> unsigned int fromJSON<unsigned int>(W<unsigned int> v, json &obj) {
40 return obj.get<unsigned int>();
41}
42
diff --git a/ddl/lib/RT.hpp b/ddl/lib/RT.hpp
new file mode 100644
index 0000000..2e1e652
--- /dev/null
+++ b/ddl/lib/RT.hpp
@@ -0,0 +1,188 @@
1#ifndef HEADER_RT_H
2#define HEADER_RT_H
3
4#include <vector>
5#include <map>
6#include <string>
7
8#include "json.hpp"
9
10using json = nlohmann::json;
11
12typedef int Int;
13typedef int Int32;
14typedef unsigned int Word;
15typedef unsigned int Word32;
16typedef float Float;
17typedef bool Bool;
18typedef std::string String;
19
20template<typename T1>
21struct Maybe
22{
23 T1 data;
24 bool valid;
25};
26
27template<typename T>
28struct V2 { T x,y; };
29
30template<typename T>
31struct V3 { T x,y,z; };
32
33template<typename T>
34struct V4 { T x,y,z,w; };
35
36typedef struct V2<Int> V2I;
37typedef struct V2<Word> V2U;
38typedef struct V2<Float> V2F;
39typedef struct V2<Bool> V2B;
40
41typedef struct V3<Int> V3I;
42typedef struct V3<Word> V3U;
43typedef struct V3<Float> V3F;
44typedef struct V3<Bool> V3B;
45
46typedef struct V4<Int> V4I;
47typedef struct V4<Word> V4U;
48typedef struct V4<Float> V4F;
49typedef struct V4<Bool> V4B;
50
51typedef struct V2<V2F> M22F;
52typedef struct V2<V3F> M32F;
53typedef struct V2<V4F> M42F;
54typedef struct V3<V2F> M23F;
55typedef struct V3<V3F> M33F;
56typedef struct V3<V4F> M43F;
57typedef struct V4<V2F> M24F;
58typedef struct V4<V3F> M34F;
59typedef struct V4<V4F> M44F;
60
61
62template<typename T>
63json toJSON(T &v);
64
65template<typename any>
66json toJSON(Maybe<any> &v) {
67 if (v.valid) {
68 return toJSON(v.data);
69 }
70 return json();
71}
72
73template<typename any>
74json toJSON(V2<any> &v) {
75 json obj({});
76 obj["x"] = toJSON(v.x);
77 obj["y"] = toJSON(v.y);
78 return obj;
79}
80
81template<typename any>
82json toJSON(V3<any> &v) {
83 json obj({});
84 obj["x"] = toJSON(v.x);
85 obj["y"] = toJSON(v.y);
86 obj["z"] = toJSON(v.z);
87 return obj;
88}
89
90template<typename any>
91json toJSON(V4<any> &v) {
92 json obj({});
93 obj["x"] = toJSON(v.x);
94 obj["y"] = toJSON(v.y);
95 obj["z"] = toJSON(v.z);
96 obj["w"] = toJSON(v.w);
97 return obj;
98}
99
100template<typename any>
101json toJSON(std::vector<any> &v) {
102 json obj = json::array();
103 for (any i : v) {
104 obj.push_back(toJSON(i));
105 }
106 return obj;
107}
108
109template<typename v>
110json toJSON(std::map<String,v> &value) {
111 json obj({});
112 for(auto i : value) {
113 obj[i.first] = toJSON(i.second);
114 }
115 return obj;
116}
117
118template<typename T>
119struct W {};
120
121template<typename T>
122T fromJSON(W<T> w, json &obj);
123
124template<typename any>
125Maybe<any> fromJSON(W<Maybe<any>> v, json &obj) {
126 Maybe<any> a;
127 if (obj.is_null()) {
128 a.valid = false;
129 } else {
130 a.valid = true;
131 a.data = fromJSON(W<any>(),obj);
132 }
133 return a;
134}
135
136template<typename any>
137V2<any> fromJSON(W<V2<any>> v, json &obj) {
138 V2<any> a;
139 a.x = fromJSON(W<any>(), obj["x"]);
140 a.y = fromJSON(W<any>(), obj["y"]);
141 return a;
142}
143
144template<typename any>
145V3<any> fromJSON(W<V3<any>> v, json &obj) {
146 V3<any> a;
147 a.x = fromJSON(W<any>(), obj["x"]);
148 a.y = fromJSON(W<any>(), obj["y"]);
149 a.z = fromJSON(W<any>(), obj["z"]);
150 return a;
151}
152
153template<typename any>
154V4<any> fromJSON(W<V4<any>> v, json &obj) {
155 V4<any> a;
156 a.x = fromJSON(W<any>(), obj["x"]);
157 a.y = fromJSON(W<any>(), obj["y"]);
158 a.z = fromJSON(W<any>(), obj["z"]);
159 a.w = fromJSON(W<any>(), obj["w"]);
160 return a;
161}
162
163template<typename any>
164std::vector<any> fromJSON(W<std::vector<any>> v, json &obj) {
165 std::vector<any> a;
166 for (json::iterator it = obj.begin(); it != obj.end(); ++it) {
167 a.push_back(fromJSON(W<any>(),*it));
168 }
169 return a;
170}
171
172template<typename v>
173std::map<String,v> fromJSON(W<std::map<String,v>> value, json &obj) {
174 std::map<String,v> a;
175 for (json::iterator it = obj.begin(); it != obj.end(); ++it) {
176 a[it.key()] = fromJSON(W<v>(),it.value());
177 }
178 return a;
179}
180
181/*
182template<typename k, typename v>
183std::map<k,v> fromJSON(W<std::map<k,v>> value, json &obj) {
184 std::map<k,v> a;
185 return a;
186}
187*/
188#endif \ No newline at end of file
diff --git a/ddl/lib/json.hpp b/ddl/lib/json.hpp
new file mode 100644
index 0000000..bdea958
--- /dev/null
+++ b/ddl/lib/json.hpp
@@ -0,0 +1,7307 @@
1/*!
2@mainpage
3
4These pages contain the API documentation of JSON for Modern C++, a C++11
5header-only JSON class.
6
7Class @ref nlohmann::basic_json is a good entry point for the documentation.
8
9@copyright The code is licensed under the [MIT
10 License](http://opensource.org/licenses/MIT):
11 <br>
12 Copyright &copy; 2013-2015 Niels Lohmann.
13 <br>
14 Permission is hereby granted, free of charge, to any person
15 obtaining a copy of this software and associated documentation files
16 (the "Software"), to deal in the Software without restriction,
17 including without limitation the rights to use, copy, modify, merge,
18 publish, distribute, sublicense, and/or sell copies of the Software,
19 and to permit persons to whom the Software is furnished to do so,
20 subject to the following conditions:
21 <br>
22 The above copyright notice and this permission notice shall be
23 included in all copies or substantial portions of the Software.
24 <br>
25 THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
26 EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
27 MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
28 NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS
29 BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN
30 ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN
31 CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
32 SOFTWARE.
33
34@author [Niels Lohmann](http://nlohmann.me)
35@see https://github.com/nlohmann/json to download the source code
36*/
37
38#ifndef NLOHMANN_JSON_HPP
39#define NLOHMANN_JSON_HPP
40
41#include <algorithm>
42#include <array>
43#include <ciso646>
44#include <cmath>
45#include <cstdio>
46#include <functional>
47#include <initializer_list>
48#include <iomanip>
49#include <iostream>
50#include <iterator>
51#include <limits>
52#include <map>
53#include <memory>
54#include <sstream>
55#include <string>
56#include <type_traits>
57#include <utility>
58#include <vector>
59
60// enable ssize_t on MinGW
61#ifdef __GNUC__
62 #ifdef __MINGW32__
63 #include <sys/types.h>
64 #endif
65#endif
66
67// enable ssize_t for MSVC
68#ifdef _MSC_VER
69 #include <basetsd.h>
70 using ssize_t = SSIZE_T;
71#endif
72
73/*!
74@brief namespace for Niels Lohmann
75@see https://github.com/nlohmann
76*/
77namespace nlohmann
78{
79
80
81/*!
82@brief unnamed namespace with internal helper functions
83*/
84namespace
85{
86/*!
87@brief Helper to determine whether there's a key_type for T.
88@sa http://stackoverflow.com/a/7728728/266378
89*/
90template<typename T>
91struct has_mapped_type
92{
93 private:
94 template<typename C> static char test(typename C::mapped_type*);
95 template<typename C> static int test(...);
96 public:
97 enum { value = sizeof(test<T>(0)) == sizeof(char) };
98};
99
100/// "equality" comparison for floating point numbers
101template<typename T>
102static bool approx(const T a, const T b)
103{
104 return not (a > b or a < b);
105}
106}
107
108/*!
109@brief a class to store JSON values
110
111@tparam ObjectType type for JSON objects (@c std::map by default; will be used
112in @ref object_t)
113@tparam ArrayType type for JSON arrays (@c std::vector by default; will be used
114in @ref array_t)
115@tparam StringType type for JSON strings and object keys (@c std::string by
116default; will be used in @ref string_t)
117@tparam BooleanType type for JSON booleans (@c `bool` by default; will be used
118in @ref boolean_t)
119@tparam NumberIntegerType type for JSON integer numbers (@c `int64_t` by
120default; will be used in @ref number_integer_t)
121@tparam NumberFloatType type for JSON floating-point numbers (@c `double` by
122default; will be used in @ref number_float_t)
123@tparam AllocatorType type of the allocator to use (@c `std::allocator` by
124default)
125
126@requirement The class satisfies the following concept requirements:
127- Basic
128 - [DefaultConstructible](http://en.cppreference.com/w/cpp/concept/DefaultConstructible):
129 JSON values can be default constructed. The result will be a JSON null value.
130 - [MoveConstructible](http://en.cppreference.com/w/cpp/concept/MoveConstructible):
131 A JSON value can be constructed from an rvalue argument.
132 - [CopyConstructible](http://en.cppreference.com/w/cpp/concept/CopyConstructible):
133 A JSON value can be copy-constrcuted from an lvalue expression.
134 - [MoveAssignable](http://en.cppreference.com/w/cpp/concept/MoveAssignable):
135 A JSON value van be assigned from an rvalue argument.
136 - [CopyAssignable](http://en.cppreference.com/w/cpp/concept/CopyAssignable):
137 A JSON value can be copy-assigned from an lvalue expression.
138 - [Destructible](http://en.cppreference.com/w/cpp/concept/Destructible):
139 JSON values can be destructed.
140- Layout
141 - [StandardLayoutType](http://en.cppreference.com/w/cpp/concept/StandardLayoutType):
142 JSON values have
143 [standard layout](http://en.cppreference.com/w/cpp/language/data_members#Standard_layout):
144 All non-static data members are private and standard layout types, the class
145 has no virtual functions or (virtual) base classes.
146- Library-wide
147 - [EqualityComparable](http://en.cppreference.com/w/cpp/concept/EqualityComparable):
148 JSON values can be compared with `==`, see @ref
149 operator==(const_reference,const_reference).
150 - [LessThanComparable](http://en.cppreference.com/w/cpp/concept/LessThanComparable):
151 JSON values can be compared with `<`, see @ref
152 operator<(const_reference,const_reference).
153 - [Swappable](http://en.cppreference.com/w/cpp/concept/Swappable):
154 Any JSON lvalue or rvalue of can be swapped with any lvalue or rvalue of
155 other compatible types, using unqualified function call @ref swap().
156 - [NullablePointer](http://en.cppreference.com/w/cpp/concept/NullablePointer):
157 JSON values can be compared against `std::nullptr_t` objects which are used
158 to model the `null` value.
159- Container
160 - [Container](http://en.cppreference.com/w/cpp/concept/Container):
161 JSON values can be used like STL containers and provide iterator access.
162 - [ReversibleContainer](http://en.cppreference.com/w/cpp/concept/ReversibleContainer);
163 JSON values can be used like STL containers and provide reverse iterator
164 access.
165
166@internal
167@note ObjectType trick from http://stackoverflow.com/a/9860911
168@endinternal
169
170@see RFC 7159 <http://rfc7159.net/rfc7159>
171*/
172template <
173 template<typename U, typename V, typename... Args> class ObjectType = std::map,
174 template<typename U, typename... Args> class ArrayType = std::vector,
175 class StringType = std::string,
176 class BooleanType = bool,
177 class NumberIntegerType = int64_t,
178 class NumberFloatType = double,
179 template<typename U> class AllocatorType = std::allocator
180 >
181class basic_json
182{
183 private:
184 /// workaround type for MSVC
185 using basic_json_t = basic_json<ObjectType,
186 ArrayType,
187 StringType,
188 BooleanType,
189 NumberIntegerType,
190 NumberFloatType,
191 AllocatorType>;
192
193 public:
194
195 /////////////////////
196 // container types //
197 /////////////////////
198
199 /// @name container types
200 /// @{
201
202 /// the type of elements in a basic_json container
203 using value_type = basic_json;
204
205 /// the type of an element reference
206 using reference = value_type&;
207
208 /// the type of an element const reference
209 using const_reference = const value_type&;
210
211 /// a type to represent differences between iterators
212 using difference_type = std::ptrdiff_t;
213
214 /// a type to represent container sizes
215 using size_type = std::size_t;
216
217 /// the allocator type
218 using allocator_type = AllocatorType<basic_json>;
219
220 /// the type of an element pointer
221 using pointer = typename std::allocator_traits<allocator_type>::pointer;
222 /// the type of an element const pointer
223 using const_pointer = typename std::allocator_traits<allocator_type>::const_pointer;
224
225 // forward declaration
226 template<typename Base> class json_reverse_iterator;
227
228 /// an iterator for a basic_json container
229 class iterator;
230 /// a const iterator for a basic_json container
231 class const_iterator;
232 /// a reverse iterator for a basic_json container
233 using reverse_iterator = json_reverse_iterator<typename basic_json::iterator>;
234 /// a const reverse iterator for a basic_json container
235 using const_reverse_iterator = json_reverse_iterator<typename basic_json::const_iterator>;
236
237 /// @}
238
239
240 /*!
241 @brief returns the allocator associated with the container
242 */
243 static allocator_type get_allocator()
244 {
245 return allocator_type();
246 }
247
248
249 ///////////////////////////
250 // JSON value data types //
251 ///////////////////////////
252
253 /// @name JSON value data types
254 /// @{
255
256 /*!
257 @brief a type for an object
258
259 [RFC 7159](http://rfc7159.net/rfc7159) describes JSON objects as follows:
260 > An object is an unordered collection of zero or more name/value pairs,
261 > where a name is a string and a value is a string, number, boolean, null,
262 > object, or array.
263
264 To store objects in C++, a type is defined by the template parameters @a
265 ObjectType which chooses the container (e.g., `std::map` or
266 `std::unordered_map`), @a StringType which chooses the type of the keys or
267 names, and @a AllocatorType which chooses the allocator to use.
268
269 #### Default type
270
271 With the default values for @a ObjectType (`std::map`), @a StringType
272 (`std::string`), and @a AllocatorType (`std::allocator`), the default value
273 for @a object_t is:
274
275 @code {.cpp}
276 std::map<
277 std::string, // key_type
278 basic_json, // value_type
279 std::less<std::string>, // key_compare
280 std::allocator<std::pair<const std::string, basic_json>> // allocator_type
281 >
282 @endcode
283
284 #### Behavior
285
286 The choice of @a object_t influences the behavior of the JSON class. With
287 the default type, objects have the following behavior:
288
289 - When all names are unique, objects will be interoperable in the sense
290 that all software implementations receiving that object will agree on the
291 name-value mappings.
292 - When the names within an object are not unique, later stored name/value
293 pairs overwrite previously stored name/value pairs, leaving the used
294 names unique. For instance, `{"key": 1}` and `{"key": 2, "key": 1}` will
295 be treated as equal and both stored as `{"key": 1}`.
296 - Internally, name/value pairs are stored in lexicographical order of the
297 names. Objects will also be serialized (see @ref dump) in this order. For
298 instance, `{"b": 1, "a": 2}` and `{"a": 2, "b": 1}` will be stored and
299 serialized as `{"a": 2, "b": 1}`.
300 - When comparing objects, the order of the name/value pairs is irrelevant.
301 This makes objects interoperable in the sense that they will not be
302 affected by these differences. For instance, `{"b": 1, "a": 2}` and
303 `{"a": 2, "b": 1}` will be treated as equal.
304
305 #### Limits
306
307 [RFC 7159](http://rfc7159.net/rfc7159) specifies:
308 > An implementation may set limits on the maximum depth of nesting.
309
310 In this class, the object's limit of nesting is not constraint explicitly.
311 However, a maximum depth of nesting may be introduced by the compiler or
312 runtime environment. A theoretical limit can be queried by calling the @ref
313 max_size function of a JSON object.
314
315 #### Storage
316
317 Objects are stored as pointers in a `basic_json` type. That is, for any
318 access to object values, a pointer of type `object_t*` must be dereferenced.
319
320 @sa array_t
321 */
322 using object_t = ObjectType<StringType,
323 basic_json,
324 std::less<StringType>,
325 AllocatorType<std::pair<const StringType,
326 basic_json>>>;
327
328 /*!
329 @brief a type for an array
330
331 [RFC 7159](http://rfc7159.net/rfc7159) describes JSON arrays as follows:
332 > An array is an ordered sequence of zero or more values.
333
334 To store objects in C++, a type is defined by the template parameters @a
335 ArrayType which chooses the container (e.g., `std::vector` or `std::list`)
336 and @a AllocatorType which chooses the allocator to use.
337
338 #### Default type
339
340 With the default values for @a ArrayType (`std::vector`) and @a
341 AllocatorType (`std::allocator`), the default value for @a array_t is:
342
343 @code {.cpp}
344 std::vector<
345 basic_json, // value_type
346 std::allocator<basic_json> // allocator_type
347 >
348 @endcode
349
350 #### Limits
351
352 [RFC 7159](http://rfc7159.net/rfc7159) specifies:
353 > An implementation may set limits on the maximum depth of nesting.
354
355 In this class, the array's limit of nesting is not constraint explicitly.
356 However, a maximum depth of nesting may be introduced by the compiler or
357 runtime environment. A theoretical limit can be queried by calling the @ref
358 max_size function of a JSON array.
359
360 #### Storage
361
362 Arrays are stored as pointers in a `basic_json` type. That is, for any
363 access to array values, a pointer of type `array_t*` must be dereferenced.
364 */
365 using array_t = ArrayType<basic_json, AllocatorType<basic_json>>;
366
367 /*!
368 @brief a type for a string
369
370 [RFC 7159](http://rfc7159.net/rfc7159) describes JSON strings as follows:
371 > A string is a sequence of zero or more Unicode characters.
372
373 To store objects in C++, a type is defined by the template parameters @a
374 StringType which chooses the container (e.g., `std::string`) to use.
375
376 Unicode values are split by the JSON class into byte-sized characters
377 during deserialization.
378
379 #### Default type
380
381 With the default values for @a StringType (`std::string`), the default
382 value for @a string_t is:
383
384 @code {.cpp}
385 std::string
386 @endcode
387
388 #### String comparison
389
390 [RFC 7159](http://rfc7159.net/rfc7159) states:
391 > Software implementations are typically required to test names of object
392 > members for equality. Implementations that transform the textual
393 > representation into sequences of Unicode code units and then perform the
394 > comparison numerically, code unit by code unit, are interoperable in the
395 > sense that implementations will agree in all cases on equality or
396 > inequality of two strings. For example, implementations that compare
397 > strings with escaped characters unconverted may incorrectly find that
398 > `"a\\b"` and `"a\u005Cb"` are not equal.
399
400 This implementation is interoperable as it does compare strings code unit
401 by code unit.
402
403 #### Storage
404
405 String values are stored as pointers in a `basic_json` type. That is, for
406 any access to string values, a pointer of type `string_t*` must be
407 dereferenced.
408 */
409 using string_t = StringType;
410
411 /*!
412 @brief a type for a boolean
413
414 [RFC 7159](http://rfc7159.net/rfc7159) implicitly describes a boolean as a
415 type which differentiates the two literals `true` and `false`.
416
417 To store objects in C++, a type is defined by the template parameter @a
418 BooleanType which chooses the type to use.
419
420 #### Default type
421
422 With the default values for @a BooleanType (`bool`), the default value for
423 @a boolean_t is:
424
425 @code {.cpp}
426 bool
427 @endcode
428
429 #### Storage
430
431 Boolean values are stored directly inside a `basic_json` type.
432 */
433 using boolean_t = BooleanType;
434
435 /*!
436 @brief a type for a number (integer)
437
438 [RFC 7159](http://rfc7159.net/rfc7159) describes numbers as follows:
439 > The representation of numbers is similar to that used in most programming
440 > languages. A number is represented in base 10 using decimal digits. It
441 > contains an integer component that may be prefixed with an optional minus
442 > sign, which may be followed by a fraction part and/or an exponent part.
443 > Leading zeros are not allowed. (...) Numeric values that cannot be
444 > represented in the grammar below (such as Infinity and NaN) are not
445 > permitted.
446
447 This description includes both integer and floating-point numbers. However,
448 C++ allows more precise storage if it is known whether the number is an
449 integer or a floating-point number. Therefore, two different types, @ref
450 number_integer_t and @ref number_float_t are used.
451
452 To store integer numbers in C++, a type is defined by the template
453 parameter @a NumberIntegerType which chooses the type to use.
454
455 #### Default type
456
457 With the default values for @a NumberIntegerType (`int64_t`), the default
458 value for @a number_integer_t is:
459
460 @code {.cpp}
461 int64_t
462 @endcode
463
464 #### Default behavior
465
466 - The restrictions about leading zeros is not enforced in C++. Instead,
467 leading zeros in integer literals lead to an interpretation as octal
468 number. Internally, the value will be stored as decimal number. For
469 instance, the C++ integer literal `010` will be serialized to `8`. During
470 deserialization, leading zeros yield an error.
471 - Not-a-number (NaN) values will be serialized to `null`.
472
473 #### Limits
474
475 [RFC 7159](http://rfc7159.net/rfc7159) specifies:
476 > An implementation may set limits on the range and precision of numbers.
477
478 When the default type is used, the maximal integer number that can be
479 stored is `9223372036854775807` (INT64_MAX) and the minimal integer number
480 that can be stored is `-9223372036854775808` (INT64_MIN). Integer numbers
481 that are out of range will yield over/underflow when used in a constructor.
482 During deserialization, too large or small integer numbers will be
483 automatically be stored as @ref number_float_t.
484
485 [RFC 7159](http://rfc7159.net/rfc7159) further states:
486 > Note that when such software is used, numbers that are integers and are
487 > in the range \f$[-2^{53}+1, 2^{53}-1]\f$ are interoperable in the sense
488 > that implementations will agree exactly on their numeric values.
489
490 As this range is a subrange of the exactly supported range [INT64_MIN,
491 INT64_MAX], this class's integer type is interoperable.
492
493 #### Storage
494
495 Integer number values are stored directly inside a `basic_json` type.
496 */
497 using number_integer_t = NumberIntegerType;
498
499 /*!
500 @brief a type for a number (floating-point)
501
502 [RFC 7159](http://rfc7159.net/rfc7159) describes numbers as follows:
503 > The representation of numbers is similar to that used in most programming
504 > languages. A number is represented in base 10 using decimal digits. It
505 > contains an integer component that may be prefixed with an optional minus
506 > sign, which may be followed by a fraction part and/or an exponent part.
507 > Leading zeros are not allowed. (...) Numeric values that cannot be
508 > represented in the grammar below (such as Infinity and NaN) are not
509 > permitted.
510
511 This description includes both integer and floating-point numbers. However,
512 C++ allows more precise storage if it is known whether the number is an
513 integer or a floating-point number. Therefore, two different types, @ref
514 number_integer_t and @ref number_float_t are used.
515
516 To store floating-point numbers in C++, a type is defined by the template
517 parameter @a NumberFloatType which chooses the type to use.
518
519 #### Default type
520
521 With the default values for @a NumberFloatType (`double`), the default
522 value for @a number_float_t is:
523
524 @code {.cpp}
525 double
526 @endcode
527
528 #### Default behavior
529
530 - The restrictions about leading zeros is not enforced in C++. Instead,
531 leading zeros in floating-point literals will be ignored. Internally, the
532 value will be stored as decimal number. For instance, the C++
533 floating-point literal `01.2` will be serialized to `1.2`. During
534 deserialization, leading zeros yield an error.
535 - Not-a-number (NaN) values will be serialized to `null`.
536
537 #### Limits
538
539 [RFC 7159](http://rfc7159.net/rfc7159) states:
540 > This specification allows implementations to set limits on the range and
541 > precision of numbers accepted. Since software that implements IEEE
542 > 754-2008 binary64 (double precision) numbers is generally available and
543 > widely used, good interoperability can be achieved by implementations that
544 > expect no more precision or range than these provide, in the sense that
545 > implementations will approximate JSON numbers within the expected
546 > precision.
547
548 This implementation does exactly follow this approach, as it uses double
549 precision floating-point numbers. Note values smaller than
550 `-1.79769313486232e+308` and values greather than `1.79769313486232e+308`
551 will be stored as NaN internally and be serialized to `null`.
552
553 #### Storage
554
555 Floating-point number values are stored directly inside a `basic_json` type.
556 */
557 using number_float_t = NumberFloatType;
558
559 /// @}
560
561
562 ///////////////////////////
563 // JSON type enumeration //
564 ///////////////////////////
565
566 /*!
567 @brief the JSON type enumeration
568
569 This enumeration collects the different JSON types. It is internally used
570 to distinguish the stored values, and the functions is_null, is_object,
571 is_array, is_string, is_boolean, is_number, and is_discarded rely on it.
572 */
573 enum class value_t : uint8_t
574 {
575 null, ///< null value
576 object, ///< object (unordered set of name/value pairs)
577 array, ///< array (ordered collection of values)
578 string, ///< string value
579 boolean, ///< boolean value
580 number_integer, ///< number value (integer)
581 number_float, ///< number value (floating-point)
582 discarded ///< discarded by the the parser callback function
583 };
584
585
586 private:
587 ////////////////////////
588 // JSON value storage //
589 ////////////////////////
590
591 /// a JSON value
592 union json_value
593 {
594 /// object (stored with pointer to save storage)
595 object_t* object;
596 /// array (stored with pointer to save storage)
597 array_t* array;
598 /// string (stored with pointer to save storage)
599 string_t* string;
600 /// boolean
601 boolean_t boolean;
602 /// number (integer)
603 number_integer_t number_integer;
604 /// number (floating-point)
605 number_float_t number_float;
606
607 /// default constructor (for null values)
608 json_value() noexcept = default;
609 /// constructor for booleans
610 json_value(boolean_t v) noexcept : boolean(v) {}
611 /// constructor for numbers (integer)
612 json_value(number_integer_t v) noexcept : number_integer(v) {}
613 /// constructor for numbers (floating-point)
614 json_value(number_float_t v) noexcept : number_float(v) {}
615 /// constructor for empty values of a given type
616 json_value(value_t t)
617 {
618 switch (t)
619 {
620 case (value_t::null):
621 case (value_t::discarded):
622 {
623 break;
624 }
625
626 case (value_t::object):
627 {
628 AllocatorType<object_t> alloc;
629 object = alloc.allocate(1);
630 alloc.construct(object);
631 break;
632 }
633
634 case (value_t::array):
635 {
636 AllocatorType<array_t> alloc;
637 array = alloc.allocate(1);
638 alloc.construct(array);
639 break;
640 }
641
642 case (value_t::string):
643 {
644 AllocatorType<string_t> alloc;
645 string = alloc.allocate(1);
646 alloc.construct(string, "");
647 break;
648 }
649
650 case (value_t::boolean):
651 {
652 boolean = boolean_t(false);
653 break;
654 }
655
656 case (value_t::number_integer):
657 {
658 number_integer = number_integer_t(0);
659 break;
660 }
661
662 case (value_t::number_float):
663 {
664 number_float = number_float_t(0.0);
665 break;
666 }
667 }
668 }
669
670 /// constructor for strings
671 json_value(const string_t& value)
672 {
673 AllocatorType<string_t> alloc;
674 string = alloc.allocate(1);
675 alloc.construct(string, value);
676 }
677
678 /// constructor for objects
679 json_value(const object_t& value)
680 {
681 AllocatorType<object_t> alloc;
682 object = alloc.allocate(1);
683 alloc.construct(object, value);
684 }
685
686 /// constructor for arrays
687 json_value(const array_t& value)
688 {
689 AllocatorType<array_t> alloc;
690 array = alloc.allocate(1);
691 alloc.construct(array, value);
692 }
693 };
694
695
696 public:
697 //////////////////////////
698 // JSON parser callback //
699 //////////////////////////
700
701 /*!
702 @brief JSON callback events
703
704 This enumeration lists the parser events that can trigger calling a
705 callback function of type @ref parser_callback_t during parsing.
706 */
707 enum class parse_event_t : uint8_t
708 {
709 /// the parser read `{` and started to process a JSON object
710 object_start,
711 /// the parser read `}` and finished processing a JSON object
712 object_end,
713 /// the parser read `[` and started to process a JSON array
714 array_start,
715 /// the parser read `]` and finished processing a JSON array
716 array_end,
717 /// the parser read a key of a value in an object
718 key,
719 /// the parser finished reading a JSON value
720 value
721 };
722
723 /*!
724 @brief per-element parser callback type
725
726 With a parser callback function, the result of parsing a JSON text can be
727 influenced. When passed to @ref parse(std::istream&, parser_callback_t) or
728 @ref parse(const string_t&, parser_callback_t), it is called on certain
729 events (passed as @ref parse_event_t via parameter @a event) with a set
730 recursion depth @a depth and context JSON value @a parsed. The return value
731 of the callback function is a boolean indicating whether the element that
732 emitted the callback shall be kept or not.
733
734 We distinguish six scenarios (determined by the event type) in which the
735 callback function can be called. The following table describes the values
736 of the parameters @a depth, @a event, and @a parsed.
737
738 parameter @a event | description | parameter @a depth | parameter @a parsed
739 ------------------ | ----------- | ------------------ | -------------------
740 parse_event_t::object_start | the parser read `{` and started to process a JSON object | depth of the parent of the JSON object | a JSON value with type discarded
741 parse_event_t::key | the parser read a key of a value in an object | depth of the currently parsed JSON object | a JSON string containing the key
742 parse_event_t::object_end | the parser read `}` and finished processing a JSON object | depth of the parent of the JSON object | the parsed JSON object
743 parse_event_t::array_start | the parser read `[` and started to process a JSON array | depth of the parent of the JSON array | a JSON value with type discarded
744 parse_event_t::array_end | the parser read `]` and finished processing a JSON array | depth of the parent of the JSON array | the parsed JSON array
745 parse_event_t::value | the parser finished reading a JSON value | depth of the value | the parsed JSON value
746
747 Discarding a value (i.e., returning `false`) has different effects depending on the
748 context in which function was called:
749
750 - Discarded values in structured types are skipped. That is, the parser
751 will behave as if the discarded value was never read.
752 - In case a value outside a structured type is skipped, it is replaced with
753 `null`. This case happens if the top-level element is skipped.
754
755 @param[in] depth the depth of the recursion during parsing
756
757 @param[in] event an event of type parse_event_t indicating the context in
758 the callback function has been called
759
760 @param[in,out] parsed the current intermediate parse result; note that
761 writing to this value has no effect for parse_event_t::key events
762
763 @return Whether the JSON value which called the function during parsing
764 should be kept (`true`) or not (`false`). In the latter case, it is either
765 skipped completely or replaced by an empty discarded object.
766
767 @sa @ref parse(std::istream&, parser_callback_t) or
768 @ref parse(const string_t&, parser_callback_t) for examples
769 */
770 using parser_callback_t = std::function<bool(
771 int depth, parse_event_t event, basic_json& parsed)>;
772
773
774 //////////////////
775 // constructors //
776 //////////////////
777
778 /*!
779 @brief create an empty value with a given type
780
781 Create an empty JSON value with a given type. The value will be default
782 initialized with an empty value which depends on the type:
783
784 Value type | initial value
785 ----------- | -------------
786 null | `null`
787 boolean | `false`
788 string | `""`
789 number | `0`
790 object | `{}`
791 array | `[]`
792
793 @param[in] value the type of the value to create
794
795 @complexity Constant.
796
797 @throw std::bad_alloc if allocation for object, array, or string value
798 fails
799
800 @liveexample{The following code shows the constructor for different @ref
801 value_t values,basic_json__value_t}
802 */
803 basic_json(const value_t value)
804 : m_type(value), m_value(value)
805 {}
806
807 /*!
808 @brief create a null object (implicitly)
809
810 Create a `null` JSON value. This is the implicit version of the `null`
811 value constructor as it takes no parameters.
812
813 @complexity Constant.
814
815 @requirement This function satisfies the Container requirements:
816 - The complexity is constant.
817 - As postcondition, it holds: `basic_json().empty() == true`.
818
819 @liveexample{The following code shows the constructor for a `null` JSON
820 value.,basic_json}
821
822 @sa basic_json(std::nullptr_t)
823 */
824 basic_json() noexcept = default;
825
826 /*!
827 @brief create a null object (explicitly)
828
829 Create a `null` JSON value. This is the explicitly version of the `null`
830 value constructor as it takes a null pointer as parameter. It allows to
831 create `null` values by explicitly assigning a @c nullptr to a JSON value.
832 The passed null pointer itself is not read - it is only used to choose the
833 right constructor.
834
835 @complexity Constant.
836
837 @liveexample{The following code shows the constructor with null pointer
838 parameter.,basic_json__nullptr_t}
839
840 @sa basic_json()
841 */
842 basic_json(std::nullptr_t) noexcept
843 : basic_json(value_t::null)
844 {}
845
846 /*!
847 @brief create an object (explicit)
848
849 Create an object JSON value with a given content.
850
851 @param[in] value a value for the object
852
853 @complexity Linear in the size of the passed @a value.
854
855 @throw std::bad_alloc if allocation for object value fails
856
857 @liveexample{The following code shows the constructor with an @ref object_t
858 parameter.,basic_json__object_t}
859
860 @sa basic_json(const CompatibleObjectType&)
861 */
862 basic_json(const object_t& value)
863 : m_type(value_t::object), m_value(value)
864 {}
865
866 /*!
867 @brief create an object (implicit)
868
869 Create an object JSON value with a given content. This constructor allows
870 any type that can be used to construct values of type @ref object_t.
871 Examples include the types `std::map` and `std::unordered_map`.
872
873 @tparam CompatibleObjectType an object type whose `key_type` and
874 `value_type` is compatible to @ref object_t
875
876 @param[in] value a value for the object
877
878 @complexity Linear in the size of the passed @a value.
879
880 @throw std::bad_alloc if allocation for object value fails
881
882 @liveexample{The following code shows the constructor with several
883 compatible object type parameters.,basic_json__CompatibleObjectType}
884
885 @sa basic_json(const object_t&)
886 */
887 template <class CompatibleObjectType, typename
888 std::enable_if<
889 std::is_constructible<typename object_t::key_type, typename CompatibleObjectType::key_type>::value and
890 std::is_constructible<basic_json, typename CompatibleObjectType::mapped_type>::value, int>::type
891 = 0>
892 basic_json(const CompatibleObjectType& value)
893 : m_type(value_t::object)
894 {
895 AllocatorType<object_t> alloc;
896 m_value.object = alloc.allocate(1);
897 using std::begin;
898 using std::end;
899 alloc.construct(m_value.object, begin(value), end(value));
900 }
901
902 /*!
903 @brief create an array (explicit)
904
905 Create an array JSON value with a given content.
906
907 @param[in] value a value for the array
908
909 @complexity Linear in the size of the passed @a value.
910
911 @throw std::bad_alloc if allocation for array value fails
912
913 @liveexample{The following code shows the constructor with an @ref array_t
914 parameter.,basic_json__array_t}
915
916 @sa basic_json(const CompatibleArrayType&)
917 */
918 basic_json(const array_t& value)
919 : m_type(value_t::array), m_value(value)
920 {}
921
922 /*!
923 @brief create an array (implicit)
924
925 Create an array JSON value with a given content. This constructor allows
926 any type that can be used to construct values of type @ref array_t.
927 Examples include the types `std::vector`, `std::list`, and `std::set`.
928
929 @tparam CompatibleArrayType an object type whose `value_type` is compatible
930 to @ref array_t
931
932 @param[in] value a value for the array
933
934 @complexity Linear in the size of the passed @a value.
935
936 @throw std::bad_alloc if allocation for array value fails
937
938 @liveexample{The following code shows the constructor with several
939 compatible array type parameters.,basic_json__CompatibleArrayType}
940
941 @sa basic_json(const array_t&)
942 */
943 template <class CompatibleArrayType, typename
944 std::enable_if<
945 not std::is_same<CompatibleArrayType, typename basic_json_t::iterator>::value and
946 not std::is_same<CompatibleArrayType, typename basic_json_t::const_iterator>::value and
947 not std::is_same<CompatibleArrayType, typename basic_json_t::reverse_iterator>::value and
948 not std::is_same<CompatibleArrayType, typename basic_json_t::const_reverse_iterator>::value and
949 not std::is_same<CompatibleArrayType, typename array_t::iterator>::value and
950 not std::is_same<CompatibleArrayType, typename array_t::const_iterator>::value and
951 std::is_constructible<basic_json, typename CompatibleArrayType::value_type>::value, int>::type
952 = 0>
953 basic_json(const CompatibleArrayType& value)
954 : m_type(value_t::array)
955 {
956 AllocatorType<array_t> alloc;
957 m_value.array = alloc.allocate(1);
958 using std::begin;
959 using std::end;
960 alloc.construct(m_value.array, begin(value), end(value));
961 }
962
963 /*!
964 @brief create a string (explicit)
965
966 Create an string JSON value with a given content.
967
968 @param[in] value a value for the string
969
970 @complexity Linear in the size of the passed @a value.
971
972 @throw std::bad_alloc if allocation for string value fails
973
974 @liveexample{The following code shows the constructor with an @ref string_t
975 parameter.,basic_json__string_t}
976
977 @sa basic_json(const typename string_t::value_type*)
978 @sa basic_json(const CompatibleStringType&)
979 */
980 basic_json(const string_t& value)
981 : m_type(value_t::string), m_value(value)
982 {}
983
984 /*!
985 @brief create a string (explicit)
986
987 Create a string JSON value with a given content.
988
989 @param[in] value a literal value for the string
990
991 @complexity Linear in the size of the passed @a value.
992
993 @throw std::bad_alloc if allocation for string value fails
994
995 @liveexample{The following code shows the constructor with string literal
996 parameter.,basic_json__string_t_value_type}
997
998 @sa basic_json(const string_t&)
999 @sa basic_json(const CompatibleStringType&)
1000 */
1001 basic_json(const typename string_t::value_type* value)
1002 : basic_json(string_t(value))
1003 {}
1004
1005 /*!
1006 @brief create a string (implicit)
1007
1008 Create a string JSON value with a given content.
1009
1010 @param[in] value a value for the string
1011
1012 @tparam CompatibleStringType an string type which is compatible to @ref
1013 string_t
1014
1015 @complexity Linear in the size of the passed @a value.
1016
1017 @throw std::bad_alloc if allocation for string value fails
1018
1019 @liveexample{The following code shows the construction of a string value
1020 from a compatible type.,basic_json__CompatibleStringType}
1021
1022 @sa basic_json(const string_t&)
1023 */
1024 template <class CompatibleStringType, typename
1025 std::enable_if<
1026 std::is_constructible<string_t, CompatibleStringType>::value, int>::type
1027 = 0>
1028 basic_json(const CompatibleStringType& value)
1029 : basic_json(string_t(value))
1030 {}
1031
1032 /*!
1033 @brief create a boolean (explicit)
1034
1035 Creates a JSON boolean type from a given value.
1036
1037 @param[in] value a boolean value to store
1038
1039 @complexity Constant.
1040
1041 @liveexample{The example below demonstrates boolean
1042 values.,basic_json__boolean_t}
1043 */
1044 basic_json(boolean_t value)
1045 : m_type(value_t::boolean), m_value(value)
1046 {}
1047
1048 /*!
1049 @brief create an integer number (explicit)
1050
1051 Create an interger number JSON value with a given content.
1052
1053 @tparam T helper type to compare number_integer_t and int (not visible in)
1054 the interface.
1055
1056 @param[in] value an integer to create a JSON number from
1057
1058 @note This constructor would have the same signature as @ref
1059 basic_json(const int value), so we need to switch this one off in case
1060 number_integer_t is the same as int. This is done via the helper type @a T.
1061
1062 @complexity Constant.
1063
1064 @liveexample{The example below shows the construction of a JSON integer
1065 number value.,basic_json__number_integer_t}
1066
1067 @sa basic_json(const int)
1068 */
1069 template<typename T,
1070 typename std::enable_if<
1071 not (std::is_same<T, int>::value)
1072 and std::is_same<T, number_integer_t>::value
1073 , int>::type = 0>
1074 basic_json(const number_integer_t value)
1075 : m_type(value_t::number_integer), m_value(value)
1076 {}
1077
1078 /*!
1079 @brief create an integer number from an enum type (explicit)
1080
1081 Create an integer number JSON value with a given content.
1082
1083 @param[in] value an integer to create a JSON number from
1084
1085 @note This constructor allows to pass enums directly to a constructor. As
1086 C++ has no way of specifying the type of an anonymous enum explicitly, we
1087 can only rely on the fact that such values implicitly convert to int. As
1088 int may already be the same type of number_integer_t, we may need to switch
1089 off the constructor @ref basic_json(const number_integer_t).
1090
1091 @complexity Constant.
1092
1093 @liveexample{The example below shows the construction of a JSON integer
1094 number value from an anonymous enum.,basic_json__const_int}
1095
1096 @sa basic_json(const number_integer_t)
1097 */
1098 basic_json(const int value)
1099 : m_type(value_t::number_integer),
1100 m_value(static_cast<number_integer_t>(value))
1101 {}
1102
1103 /*!
1104 @brief create an integer number (implicit)
1105
1106 Create an integer number JSON value with a given content. This constructor
1107 allows any type that can be used to construct values of type @ref
1108 number_integer_t. Examples may include the types `int`, `int32_t`, or
1109 `short`.
1110
1111 @tparam CompatibleNumberIntegerType an integer type which is compatible to
1112 @ref number_integer_t.
1113
1114 @param[in] value an integer to create a JSON number from
1115
1116 @complexity Constant.
1117
1118 @liveexample{The example below shows the construction of several JSON
1119 integer number values from compatible
1120 types.,basic_json__CompatibleIntegerNumberType}
1121
1122 @sa basic_json(const number_integer_t)
1123 */
1124 template<typename CompatibleNumberIntegerType, typename
1125 std::enable_if<
1126 std::is_constructible<number_integer_t, CompatibleNumberIntegerType>::value and
1127 std::numeric_limits<CompatibleNumberIntegerType>::is_integer, CompatibleNumberIntegerType>::type
1128 = 0>
1129 basic_json(const CompatibleNumberIntegerType value) noexcept
1130 : m_type(value_t::number_integer),
1131 m_value(static_cast<number_integer_t>(value))
1132 {}
1133
1134 /*!
1135 @brief create a floating-point number (explicit)
1136
1137 Create a floating-point number JSON value with a given content.
1138
1139 @param[in] value a floating-point value to create a JSON number from
1140
1141 @note RFC 7159 <http://www.rfc-editor.org/rfc/rfc7159.txt>, section 6
1142 disallows NaN values:
1143 > Numeric values that cannot be represented in the grammar below (such
1144 > as Infinity and NaN) are not permitted.
1145 In case the parameter @a value is not a number, a JSON null value is
1146 created instead.
1147
1148 @complexity Constant.
1149
1150 @liveexample{The following example creates several floating-point
1151 values.,basic_json__number_float_t}
1152 */
1153 basic_json(const number_float_t value)
1154 : m_type(value_t::number_float), m_value(value)
1155 {
1156 // replace infinity and NAN by null
1157 if (not std::isfinite(value))
1158 {
1159 m_type = value_t::null;
1160 m_value = json_value();
1161 }
1162 }
1163
1164 /*!
1165 @brief create an floating-point number (implicit)
1166
1167 Create an floating-point number JSON value with a given content. This
1168 constructor allows any type that can be used to construct values of type
1169 @ref number_float_t. Examples may include the types `float`.
1170
1171 @tparam CompatibleNumberFloatType a floating-point type which is compatible
1172 to @ref number_float_t.
1173
1174 @param[in] value a floating-point to create a JSON number from
1175
1176 @note RFC 7159 <http://www.rfc-editor.org/rfc/rfc7159.txt>, section 6
1177 disallows NaN values:
1178 > Numeric values that cannot be represented in the grammar below (such
1179 > as Infinity and NaN) are not permitted.
1180 In case the parameter @a value is not a number, a JSON null value is
1181 created instead.
1182
1183 @complexity Constant.
1184
1185 @liveexample{The example below shows the construction of several JSON
1186 floating-point number values from compatible
1187 types.,basic_json__CompatibleNumberFloatType}
1188
1189 @sa basic_json(const number_float_t)
1190 */
1191 template<typename CompatibleNumberFloatType, typename = typename
1192 std::enable_if<
1193 std::is_constructible<number_float_t, CompatibleNumberFloatType>::value and
1194 std::is_floating_point<CompatibleNumberFloatType>::value>::type
1195 >
1196 basic_json(const CompatibleNumberFloatType value) noexcept
1197 : basic_json(number_float_t(value))
1198 {}
1199
1200 /*!
1201 @brief create a container (array or object) from an initializer list
1202
1203 Creates a JSON value of type array or object from the passed initializer
1204 list @a init. In case @a type_deduction is `true` (default), the type of
1205 the JSON value to be created is deducted from the initializer list @a init
1206 according to the following rules:
1207
1208 1. If the list is empty, an empty JSON object value `{}` is created.
1209 2. If the list consists of pairs whose first element is a string, a JSON
1210 object value is created where the first elements of the pairs are treated
1211 as keys and the second elements are as values.
1212 3. In all other cases, an array is created.
1213
1214 The rules aim to create the best fit between a C++ initializer list and
1215 JSON values. The ratioinale is as follows:
1216
1217 1. The empty initializer list is written as `{}` which is exactly an empty
1218 JSON object.
1219 2. C++ has now way of describing mapped types other than to list a list of
1220 pairs. As JSON requires that keys must be of type string, rule 2 is the
1221 weakest constraint one can pose on initializer lists to interpret them as
1222 an object.
1223 3. In all other cases, the initializer list could not be interpreted as
1224 JSON object type, so interpreting it as JSON array type is safe.
1225
1226 With the rules described above, the following JSON values cannot be
1227 expressed by an initializer list:
1228
1229 - the empty array (`[]`): use @ref array(std::initializer_list<basic_json>)
1230 with an empty initializer list in this case
1231 - arrays whose elements satisfy rule 2: use @ref
1232 array(std::initializer_list<basic_json>) with the same initializer list
1233 in this case
1234
1235 @note When used without parentheses around an empty initializer list, @ref
1236 basic_json() is called instead of this function, yielding the JSON null
1237 value.
1238
1239 @param[in] init initializer list with JSON values
1240
1241 @param[in] type_deduction internal parameter; when set to `true`, the type
1242 of the JSON value is deducted from the initializer list @a init; when set
1243 to `false`, the type provided via @a manual_type is forced. This mode is
1244 used by the functions @ref array(std::initializer_list<basic_json>) and
1245 @ref object(std::initializer_list<basic_json>).
1246
1247 @param[in] manual_type internal parameter; when @a type_deduction is set to
1248 `false`, the created JSON value will use the provided type (only @ref
1249 value_t::array and @ref value_t::object are valid); when @a type_deduction
1250 is set to `true`, this parameter has no effect
1251
1252 @throw std::domain_error if @a type_deduction is `false`, @a manual_type is
1253 `value_t::object`, but @a init contains an element which is not a pair
1254 whose first element is a string
1255
1256 @complexity Linear in the size of the initializer list @a init.
1257
1258 @liveexample{The example below shows how JSON values are created from
1259 initializer lists,basic_json__list_init_t}
1260
1261 @sa basic_json array(std::initializer_list<basic_json>) - create a JSON
1262 array value from an initializer list
1263 @sa basic_json object(std::initializer_list<basic_json>) - create a JSON
1264 object value from an initializer list
1265 */
1266 basic_json(std::initializer_list<basic_json> init,
1267 bool type_deduction = true,
1268 value_t manual_type = value_t::array)
1269 {
1270 // the initializer list could describe an object
1271 bool is_object = true;
1272
1273 // check if each element is an array with two elements whose first element
1274 // is a string
1275 for (const auto& element : init)
1276 {
1277 if (element.m_type != value_t::array or element.size() != 2
1278 or element[0].m_type != value_t::string)
1279 {
1280 // we found an element that makes it impossible to use the
1281 // initializer list as object
1282 is_object = false;
1283 break;
1284 }
1285 }
1286
1287 // adjust type if type deduction is not wanted
1288 if (not type_deduction)
1289 {
1290 // if array is wanted, do not create an object though possible
1291 if (manual_type == value_t::array)
1292 {
1293 is_object = false;
1294 }
1295
1296 // if object is wanted but impossible, throw an exception
1297 if (manual_type == value_t::object and not is_object)
1298 {
1299 throw std::domain_error("cannot create object from initializer list");
1300 }
1301 }
1302
1303 if (is_object)
1304 {
1305 // the initializer list is a list of pairs -> create object
1306 m_type = value_t::object;
1307 m_value = value_t::object;
1308
1309 for (auto& element : init)
1310 {
1311 m_value.object->emplace(std::move(*(element[0].m_value.string)), std::move(element[1]));
1312 }
1313 }
1314 else
1315 {
1316 // the initializer list describes an array -> create array
1317 m_type = value_t::array;
1318 AllocatorType<array_t> alloc;
1319 m_value.array = alloc.allocate(1);
1320 alloc.construct(m_value.array, std::move(init));
1321 }
1322 }
1323
1324 /*!
1325 @brief explicitly create an array from an initializer list
1326
1327 Creates a JSON array value from a given initializer list. That is, given a
1328 list of values `a, b, c`, creates the JSON value `[a, b, c]`. If the
1329 initializer list is empty, the empty array `[]` is created.
1330
1331 @note This function is only needed to express two edge cases that cannot be
1332 realized with the initializer list constructor (@ref
1333 basic_json(std::initializer_list<basic_json>, bool, value_t)). These cases
1334 are:
1335 1. creating an array whose elements are all pairs whose first element is a
1336 string - in this case, the initializer list constructor would create an
1337 object, taking the first elements as keys
1338 2. creating an empty array - passing the empty initializer list to the
1339 initializer list constructor yields an empty object
1340
1341 @param[in] init initializer list with JSON values to create an array from
1342 (optional)
1343
1344 @return JSON array value
1345
1346 @complexity Linear in the size of @a init.
1347
1348 @liveexample{The following code shows an example for the @ref array
1349 function.,array}
1350
1351 @sa basic_json(std::initializer_list<basic_json>, bool, value_t) - create a
1352 JSON value from an initializer list
1353 @sa basic_json object(std::initializer_list<basic_json>) - create a JSON
1354 object value from an initializer list
1355 */
1356 static basic_json array(std::initializer_list<basic_json> init =
1357 std::initializer_list<basic_json>())
1358 {
1359 return basic_json(init, false, value_t::array);
1360 }
1361
1362 /*!
1363 @brief explicitly create an object from an initializer list
1364
1365 Creates a JSON object value from a given initializer list. The initializer
1366 lists elements must be pairs, and their first elments must be strings. If
1367 the initializer list is empty, the empty object `{}` is created.
1368
1369 @note This function is only added for symmetry reasons. In contrast to the
1370 related function @ref basic_json array(std::initializer_list<basic_json>),
1371 there are no cases which can only be expressed by this function. That is,
1372 any initializer list @a init can also be passed to the initializer list
1373 constructor @ref basic_json(std::initializer_list<basic_json>, bool,
1374 value_t).
1375
1376 @param[in] init initializer list to create an object from (optional)
1377
1378 @return JSON object value
1379
1380 @throw std::domain_error if @a init is not a pair whose first elements are
1381 strings; thrown by @ref basic_json(std::initializer_list<basic_json>, bool,
1382 value_t)
1383
1384 @complexity Linear in the size of @a init.
1385
1386 @liveexample{The following code shows an example for the @ref object
1387 function.,object}
1388
1389 @sa basic_json(std::initializer_list<basic_json>, bool, value_t) - create a
1390 JSON value from an initializer list
1391 @sa basic_json array(std::initializer_list<basic_json>) - create a JSON
1392 array value from an initializer list
1393 */
1394 static basic_json object(std::initializer_list<basic_json> init =
1395 std::initializer_list<basic_json>())
1396 {
1397 return basic_json(init, false, value_t::object);
1398 }
1399
1400 /*!
1401 @brief construct an array with count copies of given value
1402
1403 Constructs a JSON array value by creating @a count copies of a passed
1404 value. In case @a count is `0`, an empty array is created. As postcondition,
1405 `std::distance(begin(),end()) == count` holds.
1406
1407 @param[in] count the number of JSON copies of @a value to create
1408 @param[in] value the JSON value to copy
1409
1410 @complexity Linear in @a count.
1411
1412 @liveexample{The following code shows examples for the @ref
1413 basic_json(size_type\, const basic_json&)
1414 constructor.,basic_json__size_type_basic_json}
1415 */
1416 basic_json(size_type count, const basic_json& value)
1417 : m_type(value_t::array)
1418 {
1419 AllocatorType<array_t> alloc;
1420 m_value.array = alloc.allocate(1);
1421 alloc.construct(m_value.array, count, value);
1422 }
1423
1424 /*!
1425 @brief construct a JSON container given an iterator range
1426
1427 Constructs the JSON value with the contents of the range `[first, last)`.
1428 The semantics depends on the different types a JSON value can have:
1429 - In case of primitive types (number, boolean, or string), @a first must
1430 be `begin()` and @a last must be `end()`. In this case, the value is
1431 copied. Otherwise, std::out_of_range is thrown.
1432 - In case of structured types (array, object), the constructor behaves
1433 as similar versions for `std::vector`.
1434 - In case of a null type, std::domain_error is thrown.
1435
1436 @tparam InputIT an input iterator type (@ref iterator or @ref
1437 const_iterator)
1438
1439 @param[in] first begin of the range to copy from (included)
1440 @param[in] last end of the range to copy from (excluded)
1441
1442 @throw std::domain_error if iterators are not compatible; that is, do not
1443 belong to the same JSON value
1444 @throw std::out_of_range if iterators are for a primitive type (number,
1445 boolean, or string) where an out of range error can be detected easily
1446 @throw std::bad_alloc if allocation for object, array, or string fails
1447 @throw std::domain_error if called with a null value
1448
1449 @complexity Linear in distance between @a first and @a last.
1450
1451 @liveexample{The example below shows several ways to create JSON values by
1452 specifying a subrange with iterators.,basic_json__InputIt_InputIt}
1453 */
1454 template <class InputIT, typename
1455 std::enable_if<
1456 std::is_same<InputIT, typename basic_json_t::iterator>::value or
1457 std::is_same<InputIT, typename basic_json_t::const_iterator>::value
1458 , int>::type
1459 = 0>
1460 basic_json(InputIT first, InputIT last) : m_type(first.m_object->m_type)
1461 {
1462 // make sure iterator fits the current value
1463 if (first.m_object != last.m_object)
1464 {
1465 throw std::domain_error("iterators are not compatible");
1466 }
1467
1468 // check if iterator range is complete for primitive values
1469 switch (m_type)
1470 {
1471 case value_t::number_integer:
1472 case value_t::number_float:
1473 case value_t::boolean:
1474 case value_t::string:
1475 {
1476 if (not first.m_it.primitive_iterator.is_begin() or not last.m_it.primitive_iterator.is_end())
1477 {
1478 throw std::out_of_range("iterators out of range");
1479 }
1480 break;
1481 }
1482
1483 default:
1484 {
1485 break;
1486 }
1487 }
1488
1489 switch (m_type)
1490 {
1491 case value_t::number_integer:
1492 {
1493 m_value.number_integer = first.m_object->m_value.number_integer;
1494 break;
1495 }
1496
1497 case value_t::number_float:
1498 {
1499 m_value.number_float = first.m_object->m_value.number_float;
1500 break;
1501 }
1502
1503 case value_t::boolean:
1504 {
1505 m_value.boolean = first.m_object->m_value.boolean;
1506 break;
1507 }
1508
1509 case value_t::string:
1510 {
1511 m_value = *first.m_object->m_value.string;
1512 break;
1513 }
1514
1515 case value_t::object:
1516 {
1517 AllocatorType<object_t> alloc;
1518 m_value.object = alloc.allocate(1);
1519 alloc.construct(m_value.object, first.m_it.object_iterator, last.m_it.object_iterator);
1520 break;
1521 }
1522
1523 case value_t::array:
1524 {
1525 AllocatorType<array_t> alloc;
1526 m_value.array = alloc.allocate(1);
1527 alloc.construct(m_value.array, first.m_it.array_iterator, last.m_it.array_iterator);
1528 break;
1529 }
1530
1531 default:
1532 {
1533 throw std::domain_error("cannot use construct with iterators from " + first.m_object->type_name());
1534 }
1535 }
1536 }
1537
1538 ///////////////////////////////////////
1539 // other constructors and destructor //
1540 ///////////////////////////////////////
1541
1542 /*!
1543 @brief copy constructor
1544
1545 Creates a copy of a given JSON value.
1546
1547 @param[in] other the JSON value to copy
1548
1549 @complexity Linear in the size of @a other.
1550
1551 @requirement This function satisfies the Container requirements:
1552 - The complexity is linear.
1553 - As postcondition, it holds: `other == basic_json(other)`.
1554
1555 @throw std::bad_alloc if allocation for object, array, or string fails.
1556
1557 @liveexample{The following code shows an example for the copy
1558 constructor.,basic_json__basic_json}
1559 */
1560 basic_json(const basic_json& other)
1561 : m_type(other.m_type)
1562 {
1563 switch (m_type)
1564 {
1565 case (value_t::null):
1566 case (value_t::discarded):
1567 {
1568 break;
1569 }
1570
1571 case (value_t::object):
1572 {
1573 m_value = *other.m_value.object;
1574 break;
1575 }
1576
1577 case (value_t::array):
1578 {
1579 m_value = *other.m_value.array;
1580 break;
1581 }
1582
1583 case (value_t::string):
1584 {
1585 m_value = *other.m_value.string;
1586 break;
1587 }
1588
1589 case (value_t::boolean):
1590 {
1591 m_value = other.m_value.boolean;
1592 break;
1593 }
1594
1595 case (value_t::number_integer):
1596 {
1597 m_value = other.m_value.number_integer;
1598 break;
1599 }
1600
1601 case (value_t::number_float):
1602 {
1603 m_value = other.m_value.number_float;
1604 break;
1605 }
1606 }
1607 }
1608
1609 /*!
1610 @brief move constructor
1611
1612 Move constructor. Constructs a JSON value with the contents of the given
1613 value @a other using move semantics. It "steals" the resources from @a
1614 other and leaves it as JSON null value.
1615
1616 @param[in,out] other value to move to this object
1617
1618 @post @a other is a JSON null value
1619
1620 @complexity Constant.
1621
1622 @liveexample{The code below shows the move constructor explicitly called
1623 via std::move.,basic_json__moveconstructor}
1624 */
1625 basic_json(basic_json&& other) noexcept
1626 : m_type(std::move(other.m_type)),
1627 m_value(std::move(other.m_value))
1628 {
1629 // invalidate payload
1630 other.m_type = value_t::null;
1631 other.m_value = {};
1632 }
1633
1634 /*!
1635 @brief copy assignment
1636
1637 Copy assignment operator. Copies a JSON value via the "copy and swap"
1638 strategy: It is expressed in terms of the copy constructor, destructor, and
1639 the swap() member function.
1640
1641 @param[in] other value to copy from
1642
1643 @complexity Linear.
1644
1645 @requirement This function satisfies the Container requirements:
1646 - The complexity is linear.
1647
1648 @liveexample{The code below shows and example for the copy assignment. It
1649 creates a copy of value `a` which is then swapped with `b`. Finally\, the
1650 copy of `a` (which is the null value after the swap) is
1651 destroyed.,basic_json__copyassignment}
1652 */
1653 reference& operator=(basic_json other) noexcept (
1654 std::is_nothrow_move_constructible<value_t>::value and
1655 std::is_nothrow_move_assignable<value_t>::value and
1656 std::is_nothrow_move_constructible<json_value>::value and
1657 std::is_nothrow_move_assignable<json_value>::value
1658 )
1659 {
1660 using std::swap;
1661 std::swap(m_type, other.m_type);
1662 std::swap(m_value, other.m_value);
1663 return *this;
1664 }
1665
1666 /*!
1667 @brief destructor
1668
1669 Destroys the JSON value and frees all allocated memory.
1670
1671 @complexity Linear.
1672
1673 @requirement This function satisfies the Container requirements:
1674 - The complexity is linear.
1675 - All stored elements are destroyed and all memory is freed.
1676 */
1677 ~basic_json()
1678 {
1679 switch (m_type)
1680 {
1681 case (value_t::object):
1682 {
1683 AllocatorType<object_t> alloc;
1684 alloc.destroy(m_value.object);
1685 alloc.deallocate(m_value.object, 1);
1686 m_value.object = nullptr;
1687 break;
1688 }
1689
1690 case (value_t::array):
1691 {
1692 AllocatorType<array_t> alloc;
1693 alloc.destroy(m_value.array);
1694 alloc.deallocate(m_value.array, 1);
1695 m_value.array = nullptr;
1696 break;
1697 }
1698
1699 case (value_t::string):
1700 {
1701 AllocatorType<string_t> alloc;
1702 alloc.destroy(m_value.string);
1703 alloc.deallocate(m_value.string, 1);
1704 m_value.string = nullptr;
1705 break;
1706 }
1707
1708 default:
1709 {
1710 // all other types need no specific destructor
1711 break;
1712 }
1713 }
1714 }
1715
1716
1717 public:
1718 ///////////////////////
1719 // object inspection //
1720 ///////////////////////
1721
1722 /// @name object inspection
1723 /// @{
1724
1725 /*!
1726 @brief serialization
1727
1728 Serialization function for JSON values. The function tries to mimick
1729 Python's @p json.dumps() function, and currently supports its @p indent
1730 parameter.
1731
1732 @param[in] indent if indent is nonnegative, then array elements and object
1733 members will be pretty-printed with that indent level. An indent level of 0
1734 will only insert newlines. -1 (the default) selects the most compact
1735 representation
1736
1737 @return string containing the serialization of the JSON value
1738
1739 @complexity Linear.
1740
1741 @liveexample{The following example shows the effect of different @a indent
1742 parameters to the result of the serializaion.,dump}
1743
1744 @see https://docs.python.org/2/library/json.html#json.dump
1745 */
1746 string_t dump(const int indent = -1) const
1747 {
1748 std::stringstream ss;
1749
1750 if (indent >= 0)
1751 {
1752 dump(ss, true, static_cast<unsigned int>(indent));
1753 }
1754 else
1755 {
1756 dump(ss, false, 0);
1757 }
1758
1759 return ss.str();
1760 }
1761
1762 /*!
1763 @brief return the type of the JSON value (explicit)
1764
1765 Return the type of the JSON value as a value from the @ref value_t
1766 enumeration.
1767
1768 @return the type of the JSON value
1769
1770 @complexity Constant.
1771
1772 @liveexample{The following code exemplifies @ref type() for all JSON
1773 types.,type}
1774 */
1775 value_t type() const noexcept
1776 {
1777 return m_type;
1778 }
1779
1780 /*!
1781 @brief return whether type is primitive
1782
1783 This function returns true iff the JSON type is primitive (string, number,
1784 boolean, or null).
1785
1786 @return `true` if type is primitive (string, number, boolean, or null),
1787 `false` otherwise.
1788
1789 @complexity Constant.
1790
1791 @liveexample{The following code exemplifies @ref is_primitive for all JSON
1792 types.,is_primitive}
1793 */
1794 bool is_primitive() const noexcept
1795 {
1796 return is_null() or is_string() or is_boolean() or is_number();
1797 }
1798
1799 /*!
1800 @brief return whether type is structured
1801
1802 This function returns true iff the JSON type is structured (array or
1803 object).
1804
1805 @return `true` if type is structured (array or object), `false` otherwise.
1806
1807 @complexity Constant.
1808
1809 @liveexample{The following code exemplifies @ref is_structured for all JSON
1810 types.,is_structured}
1811 */
1812 bool is_structured() const noexcept
1813 {
1814 return is_array() or is_object();
1815 }
1816
1817 /*!
1818 @brief return whether value is null
1819
1820 This function returns true iff the JSON value is null.
1821
1822 @return `true` if type is null, `false` otherwise.
1823
1824 @complexity Constant.
1825
1826 @liveexample{The following code exemplifies @ref is_null for all JSON
1827 types.,is_null}
1828 */
1829 bool is_null() const noexcept
1830 {
1831 return m_type == value_t::null;
1832 }
1833
1834 /*!
1835 @brief return whether value is a boolean
1836
1837 This function returns true iff the JSON value is a boolean.
1838
1839 @return `true` if type is boolean, `false` otherwise.
1840
1841 @complexity Constant.
1842
1843 @liveexample{The following code exemplifies @ref is_boolean for all JSON
1844 types.,is_boolean}
1845 */
1846 bool is_boolean() const noexcept
1847 {
1848 return m_type == value_t::boolean;
1849 }
1850
1851 /*!
1852 @brief return whether value is a number
1853
1854 This function returns true iff the JSON value is a number. This includes
1855 both integer and floating-point values.
1856
1857 @return `true` if type is number, `false` otherwise.
1858
1859 @complexity Constant.
1860
1861 @liveexample{The following code exemplifies @ref is_number for all JSON
1862 types.,is_number}
1863 */
1864 bool is_number() const noexcept
1865 {
1866 return is_number_integer() or is_number_float();
1867 }
1868
1869 /*!
1870 @brief return whether value is an integer number
1871
1872 This function returns true iff the JSON value is an integer number. This
1873 excludes floating-point values.
1874
1875 @return `true` if type is an integer number, `false` otherwise.
1876
1877 @complexity Constant.
1878
1879 @liveexample{The following code exemplifies @ref is_number_integer for all
1880 JSON types.,is_number_integer}
1881 */
1882 bool is_number_integer() const noexcept
1883 {
1884 return m_type == value_t::number_integer;
1885 }
1886
1887 /*!
1888 @brief return whether value is a floating-point number
1889
1890 This function returns true iff the JSON value is a floating-point number.
1891 This excludes integer values.
1892
1893 @return `true` if type is a floating-point number, `false` otherwise.
1894
1895 @complexity Constant.
1896
1897 @liveexample{The following code exemplifies @ref is_number_float for all
1898 JSON types.,is_number_float}
1899 */
1900 bool is_number_float() const noexcept
1901 {
1902 return m_type == value_t::number_float;
1903 }
1904
1905 /*!
1906 @brief return whether value is an object
1907
1908 This function returns true iff the JSON value is an object.
1909
1910 @return `true` if type is object, `false` otherwise.
1911
1912 @complexity Constant.
1913
1914 @liveexample{The following code exemplifies @ref is_object for all JSON
1915 types.,is_object}
1916 */
1917 bool is_object() const noexcept
1918 {
1919 return m_type == value_t::object;
1920 }
1921
1922 /*!
1923 @brief return whether value is an array
1924
1925 This function returns true iff the JSON value is an array.
1926
1927 @return `true` if type is array, `false` otherwise.
1928
1929 @complexity Constant.
1930
1931 @liveexample{The following code exemplifies @ref is_array for all JSON
1932 types.,is_array}
1933 */
1934 bool is_array() const noexcept
1935 {
1936 return m_type == value_t::array;
1937 }
1938
1939 /*!
1940 @brief return whether value is a string
1941
1942 This function returns true iff the JSON value is a string.
1943
1944 @return `true` if type is string, `false` otherwise.
1945
1946 @complexity Constant.
1947
1948 @liveexample{The following code exemplifies @ref is_string for all JSON
1949 types.,is_string}
1950 */
1951 bool is_string() const noexcept
1952 {
1953 return m_type == value_t::string;
1954 }
1955
1956 /*!
1957 @brief return whether value is discarded
1958
1959 This function returns true iff the JSON value was discarded during parsing
1960 with a callback function (see @ref parser_callback_t).
1961
1962 @note This function will always be `false` for JSON values after parsing.
1963 That is, discarded values can only occur during parsing, but will be
1964 removed when inside a structured value or replaced by null in other cases.
1965
1966 @return `true` if type is discarded, `false` otherwise.
1967
1968 @complexity Constant.
1969
1970 @liveexample{The following code exemplifies @ref is_discarded for all JSON
1971 types.,is_discarded}
1972 */
1973 bool is_discarded() const noexcept
1974 {
1975 return m_type == value_t::discarded;
1976 }
1977
1978 /*!
1979 @brief return the type of the JSON value (implicit)
1980
1981 Implicitly return the type of the JSON value as a value from the @ref
1982 value_t enumeration.
1983
1984 @return the type of the JSON value
1985
1986 @complexity Constant.
1987
1988 @liveexample{The following code exemplifies the value_t operator for all
1989 JSON types.,operator__value_t}
1990 */
1991 operator value_t() const noexcept
1992 {
1993 return m_type;
1994 }
1995
1996 /// @}
1997
1998 private:
1999 //////////////////
2000 // value access //
2001 //////////////////
2002
2003 /// get an object (explicit)
2004 template <class T, typename
2005 std::enable_if<
2006 std::is_convertible<typename object_t::key_type, typename T::key_type>::value and
2007 std::is_convertible<basic_json_t, typename T::mapped_type>::value
2008 , int>::type = 0>
2009 T get_impl(T*) const
2010 {
2011 switch (m_type)
2012 {
2013 case (value_t::object):
2014 {
2015 return T(m_value.object->begin(), m_value.object->end());
2016 }
2017 default:
2018 {
2019 throw std::domain_error("type must be object, but is " + type_name());
2020 }
2021 }
2022 }
2023
2024 /// get an object (explicit)
2025 object_t get_impl(object_t*) const
2026 {
2027 switch (m_type)
2028 {
2029 case (value_t::object):
2030 {
2031 return *(m_value.object);
2032 }
2033 default:
2034 {
2035 throw std::domain_error("type must be object, but is " + type_name());
2036 }
2037 }
2038 }
2039
2040 /// get an array (explicit)
2041 template <class T, typename
2042 std::enable_if<
2043 std::is_convertible<basic_json_t, typename T::value_type>::value and
2044 not std::is_same<basic_json_t, typename T::value_type>::value and
2045 not std::is_arithmetic<T>::value and
2046 not std::is_convertible<std::string, T>::value and
2047 not has_mapped_type<T>::value
2048 , int>::type = 0>
2049 T get_impl(T*) const
2050 {
2051 switch (m_type)
2052 {
2053 case (value_t::array):
2054 {
2055 T to_vector;
2056 std::transform(m_value.array->begin(), m_value.array->end(),
2057 std::inserter(to_vector, to_vector.end()), [](basic_json i)
2058 {
2059 return i.get<typename T::value_type>();
2060 });
2061 return to_vector;
2062 }
2063 default:
2064 {
2065 throw std::domain_error("type must be array, but is " + type_name());
2066 }
2067 }
2068 }
2069
2070 /// get an array (explicit)
2071 template <class T, typename
2072 std::enable_if<
2073 std::is_convertible<basic_json_t, T>::value and
2074 not std::is_same<basic_json_t, T>::value
2075 , int>::type = 0>
2076 std::vector<T> get_impl(std::vector<T>*) const
2077 {
2078 switch (m_type)
2079 {
2080 case (value_t::array):
2081 {
2082 std::vector<T> to_vector;
2083 to_vector.reserve(m_value.array->size());
2084 std::transform(m_value.array->begin(), m_value.array->end(),
2085 std::inserter(to_vector, to_vector.end()), [](basic_json i)
2086 {
2087 return i.get<T>();
2088 });
2089 return to_vector;
2090 }
2091 default:
2092 {
2093 throw std::domain_error("type must be array, but is " + type_name());
2094 }
2095 }
2096 }
2097
2098 /// get an array (explicit)
2099 template <class T, typename
2100 std::enable_if<
2101 std::is_same<basic_json, typename T::value_type>::value and
2102 not has_mapped_type<T>::value
2103 , int>::type = 0>
2104 T get_impl(T*) const
2105 {
2106 switch (m_type)
2107 {
2108 case (value_t::array):
2109 {
2110 return T(m_value.array->begin(), m_value.array->end());
2111 }
2112 default:
2113 {
2114 throw std::domain_error("type must be array, but is " + type_name());
2115 }
2116 }
2117 }
2118
2119 /// get an array (explicit)
2120 array_t get_impl(array_t*) const
2121 {
2122 switch (m_type)
2123 {
2124 case (value_t::array):
2125 {
2126 return *(m_value.array);
2127 }
2128 default:
2129 {
2130 throw std::domain_error("type must be array, but is " + type_name());
2131 }
2132 }
2133 }
2134
2135 /// get a string (explicit)
2136 template <typename T, typename
2137 std::enable_if<
2138 std::is_convertible<string_t, T>::value
2139 , int>::type = 0>
2140 T get_impl(T*) const
2141 {
2142 switch (m_type)
2143 {
2144 case (value_t::string):
2145 {
2146 return *m_value.string;
2147 }
2148 default:
2149 {
2150 throw std::domain_error("type must be string, but is " + type_name());
2151 }
2152 }
2153 }
2154
2155 /// get a number (explicit)
2156 template<typename T, typename
2157 std::enable_if<
2158 std::is_arithmetic<T>::value
2159 , int>::type = 0>
2160 T get_impl(T*) const
2161 {
2162 switch (m_type)
2163 {
2164 case (value_t::number_integer):
2165 {
2166 return static_cast<T>(m_value.number_integer);
2167 }
2168 case (value_t::number_float):
2169 {
2170 return static_cast<T>(m_value.number_float);
2171 }
2172 default:
2173 {
2174 throw std::domain_error("type must be number, but is " + type_name());
2175 }
2176 }
2177 }
2178
2179 /// get a boolean (explicit)
2180 boolean_t get_impl(boolean_t*) const
2181 {
2182 switch (m_type)
2183 {
2184 case (value_t::boolean):
2185 {
2186 return m_value.boolean;
2187 }
2188 default:
2189 {
2190 throw std::domain_error("type must be boolean, but is " + type_name());
2191 }
2192 }
2193 }
2194
2195 /// get a pointer to the value (object)
2196 object_t* get_impl_ptr(object_t*) noexcept
2197 {
2198 return is_object() ? m_value.object : nullptr;
2199 }
2200
2201 /// get a pointer to the value (object)
2202 const object_t* get_impl_ptr(const object_t*) const noexcept
2203 {
2204 return is_object() ? m_value.object : nullptr;
2205 }
2206
2207 /// get a pointer to the value (array)
2208 array_t* get_impl_ptr(array_t*) noexcept
2209 {
2210 return is_array() ? m_value.array : nullptr;
2211 }
2212
2213 /// get a pointer to the value (array)
2214 const array_t* get_impl_ptr(const array_t*) const noexcept
2215 {
2216 return is_array() ? m_value.array : nullptr;
2217 }
2218
2219 /// get a pointer to the value (string)
2220 string_t* get_impl_ptr(string_t*) noexcept
2221 {
2222 return is_string() ? m_value.string : nullptr;
2223 }
2224
2225 /// get a pointer to the value (string)
2226 const string_t* get_impl_ptr(const string_t*) const noexcept
2227 {
2228 return is_string() ? m_value.string : nullptr;
2229 }
2230
2231 /// get a pointer to the value (boolean)
2232 boolean_t* get_impl_ptr(boolean_t*) noexcept
2233 {
2234 return is_boolean() ? &m_value.boolean : nullptr;
2235 }
2236
2237 /// get a pointer to the value (boolean)
2238 const boolean_t* get_impl_ptr(const boolean_t*) const noexcept
2239 {
2240 return is_boolean() ? &m_value.boolean : nullptr;
2241 }
2242
2243 /// get a pointer to the value (integer number)
2244 number_integer_t* get_impl_ptr(number_integer_t*) noexcept
2245 {
2246 return is_number_integer() ? &m_value.number_integer : nullptr;
2247 }
2248
2249 /// get a pointer to the value (integer number)
2250 const number_integer_t* get_impl_ptr(const number_integer_t*) const noexcept
2251 {
2252 return is_number_integer() ? &m_value.number_integer : nullptr;
2253 }
2254
2255 /// get a pointer to the value (floating-point number)
2256 number_float_t* get_impl_ptr(number_float_t*) noexcept
2257 {
2258 return is_number_float() ? &m_value.number_float : nullptr;
2259 }
2260
2261 /// get a pointer to the value (floating-point number)
2262 const number_float_t* get_impl_ptr(const number_float_t*) const noexcept
2263 {
2264 return is_number_float() ? &m_value.number_float : nullptr;
2265 }
2266
2267 public:
2268
2269 /// @name value access
2270 /// @{
2271
2272 /*!
2273 @brief get a value (explicit)
2274
2275 Explicit type conversion between the JSON value and a compatible value.
2276
2277 @tparam ValueType non-pointer type compatible to the JSON value, for
2278 instance `int` for JSON integer numbers, `bool` for JSON booleans, or
2279 `std::vector` types for JSON arrays
2280
2281 @return copy of the JSON value, converted to type @a ValueType
2282
2283 @throw std::domain_error in case passed type @a ValueType is incompatible
2284 to JSON
2285
2286 @complexity Linear in the size of the JSON value.
2287
2288 @liveexample{The example below shows serveral conversions from JSON values
2289 to other types. There a few things to note: (1) Floating-point numbers can
2290 be converted to integers\, (2) A JSON array can be converted to a standard
2291 `std::vector<short>`\, (3) A JSON object can be converted to C++
2292 assiciative containers such as `std::unordered_map<std::string\,
2293 json>`.,get__ValueType_const}
2294
2295 @internal
2296 The idea of using a casted null pointer to choose the correct
2297 implementation is from <http://stackoverflow.com/a/8315197/266378>.
2298 @endinternal
2299
2300 @sa @ref operator ValueType() const for implicit conversion
2301 @sa @ref get() for pointer-member access
2302 */
2303 template<typename ValueType, typename
2304 std::enable_if<
2305 not std::is_pointer<ValueType>::value
2306 , int>::type = 0>
2307 ValueType get() const
2308 {
2309 return get_impl(static_cast<ValueType*>(nullptr));
2310 }
2311
2312 /*!
2313 @brief get a pointer value (explicit)
2314
2315 Explicit pointer access to the internally stored JSON value. No copies are
2316 made.
2317
2318 @warning Writing data to the pointee of the result yields an undefined
2319 state.
2320
2321 @tparam PointerType pointer type; must be a pointer to @ref array_t, @ref
2322 object_t, @ref string_t, @ref boolean_t, @ref number_integer_t, or @ref
2323 number_float_t.
2324
2325 @return pointer to the internally stored JSON value if the requested pointer
2326 type @a PointerType fits to the JSON value; `nullptr` otherwise
2327
2328 @complexity Constant.
2329
2330 @liveexample{The example below shows how pointers to internal values of a
2331 JSON value can be requested. Note that no type conversions are made and a
2332 `nullptr` is returned if the value and the requested pointer type does not
2333 match.,get__PointerType}
2334
2335 @sa @ref get_ptr() for explicit pointer-member access
2336 */
2337 template<typename PointerType, typename
2338 std::enable_if<
2339 std::is_pointer<PointerType>::value
2340 , int>::type = 0>
2341 PointerType get() noexcept
2342 {
2343 // delegate the call to get_ptr
2344 return get_ptr<PointerType>();
2345 }
2346
2347 /*!
2348 @brief get a pointer value (explicit)
2349 @copydoc get()
2350 */
2351 template<typename PointerType, typename
2352 std::enable_if<
2353 std::is_pointer<PointerType>::value
2354 , int>::type = 0>
2355 const PointerType get() const noexcept
2356 {
2357 // delegate the call to get_ptr
2358 return get_ptr<PointerType>();
2359 }
2360
2361 /*!
2362 @brief get a pointer value (implicit)
2363
2364 Implict pointer access to the internally stored JSON value. No copies are
2365 made.
2366
2367 @warning Writing data to the pointee of the result yields an undefined
2368 state.
2369
2370 @tparam PointerType pointer type; must be a pointer to @ref array_t, @ref
2371 object_t, @ref string_t, @ref boolean_t, @ref number_integer_t, or @ref
2372 number_float_t.
2373
2374 @return pointer to the internally stored JSON value if the requested pointer
2375 type @a PointerType fits to the JSON value; `nullptr` otherwise
2376
2377 @complexity Constant.
2378
2379 @liveexample{The example below shows how pointers to internal values of a
2380 JSON value can be requested. Note that no type conversions are made and a
2381 `nullptr` is returned if the value and the requested pointer type does not
2382 match.,get_ptr}
2383 */
2384 template<typename PointerType, typename
2385 std::enable_if<
2386 std::is_pointer<PointerType>::value
2387 , int>::type = 0>
2388 PointerType get_ptr() noexcept
2389 {
2390 // delegate the call to get_impl_ptr<>()
2391 return get_impl_ptr(static_cast<PointerType>(nullptr));
2392 }
2393
2394 /*!
2395 @brief get a pointer value (implicit)
2396 @copydoc get_ptr()
2397 */
2398 template<typename PointerType, typename
2399 std::enable_if<
2400 std::is_pointer<PointerType>::value
2401 and std::is_const<PointerType>::value
2402 , int>::type = 0>
2403 const PointerType get_ptr() const noexcept
2404 {
2405 // delegate the call to get_impl_ptr<>() const
2406 return get_impl_ptr(static_cast<const PointerType>(nullptr));
2407 }
2408
2409 /*!
2410 @brief get a value (implicit)
2411
2412 Implict type conversion between the JSON value and a compatible value. The
2413 call is realized by calling @ref get() const.
2414
2415 @tparam ValueType non-pointer type compatible to the JSON value, for
2416 instance `int` for JSON integer numbers, `bool` for JSON booleans, or
2417 `std::vector` types for JSON arrays
2418
2419 @return copy of the JSON value, converted to type @a ValueType
2420
2421 @throw std::domain_error in case passed type @a ValueType is incompatible
2422 to JSON, thrown by @ref get() const
2423
2424 @complexity Linear in the size of the JSON value.
2425
2426 @liveexample{The example below shows serveral conversions from JSON values
2427 to other types. There a few things to note: (1) Floating-point numbers can
2428 be converted to integers\, (2) A JSON array can be converted to a standard
2429 `std::vector<short>`\, (3) A JSON object can be converted to C++
2430 assiciative containers such as `std::unordered_map<std::string\,
2431 json>`.,operator__ValueType}
2432 */
2433 template<typename ValueType, typename
2434 std::enable_if<
2435 not std::is_pointer<ValueType>::value
2436 , int>::type = 0>
2437 operator ValueType() const
2438 {
2439 // delegate the call to get<>() const
2440 return get<ValueType>();
2441 }
2442
2443 /// @}
2444
2445
2446 ////////////////////
2447 // element access //
2448 ////////////////////
2449
2450 /// @name element access
2451 /// @{
2452
2453 /*!
2454 @brief access specified array element with bounds checking
2455
2456 Returns a reference to the element at specified location @a idx, with
2457 bounds checking.
2458
2459 @param[in] idx index of the element to access
2460
2461 @return reference to the element at index @a idx
2462
2463 @throw std::domain_error if JSON is not an array
2464 @throw std::out_of_range if the index @a idx is out of range of the array;
2465 that is, `idx >= size()`
2466
2467 @complexity Constant.
2468
2469 @liveexample{The example below shows how array elements can be read and
2470 written using at.,at__size_type}
2471 */
2472 reference at(size_type idx)
2473 {
2474 // at only works for arrays
2475 if (m_type != value_t::array)
2476 {
2477 throw std::domain_error("cannot use at() with " + type_name());
2478 }
2479
2480 return m_value.array->at(idx);
2481 }
2482
2483 /*!
2484 @brief access specified array element with bounds checking
2485
2486 Returns a const reference to the element at specified location @a idx, with
2487 bounds checking.
2488
2489 @param[in] idx index of the element to access
2490
2491 @return const reference to the element at index @a idx
2492
2493 @throw std::domain_error if JSON is not an array
2494 @throw std::out_of_range if the index @a idx is out of range of the array;
2495 that is, `idx >= size()`
2496
2497 @complexity Constant.
2498
2499 @liveexample{The example below shows how array elements can be read using
2500 at.,at__size_type_const}
2501 */
2502 const_reference at(size_type idx) const
2503 {
2504 // at only works for arrays
2505 if (m_type != value_t::array)
2506 {
2507 throw std::domain_error("cannot use at() with " + type_name());
2508 }
2509
2510 return m_value.array->at(idx);
2511 }
2512
2513 /*!
2514 @brief access specified object element with bounds checking
2515
2516 Returns a reference to the element at with specified key @a key, with
2517 bounds checking.
2518
2519 @param[in] key key of the element to access
2520
2521 @return reference to the element at key @a key
2522
2523 @throw std::domain_error if JSON is not an object
2524 @throw std::out_of_range if the key @a key is is not stored in the object;
2525 that is, `find(key) == end()`
2526
2527 @complexity Logarithmic in the size of the container.
2528
2529 @liveexample{The example below shows how object elements can be read and
2530 written using at.,at__object_t_key_type}
2531 */
2532 reference at(const typename object_t::key_type& key)
2533 {
2534 // at only works for objects
2535 if (m_type != value_t::object)
2536 {
2537 throw std::domain_error("cannot use at() with " + type_name());
2538 }
2539
2540 return m_value.object->at(key);
2541 }
2542
2543 /*!
2544 @brief access specified object element with bounds checking
2545
2546 Returns a const reference to the element at with specified key @a key, with
2547 bounds checking.
2548
2549 @param[in] key key of the element to access
2550
2551 @return const reference to the element at key @a key
2552
2553 @throw std::domain_error if JSON is not an object
2554 @throw std::out_of_range if the key @a key is is not stored in the object;
2555 that is, `find(key) == end()`
2556
2557 @complexity Logarithmic in the size of the container.
2558
2559 @liveexample{The example below shows how object elements can be read using
2560 at.,at__object_t_key_type_const}
2561 */
2562 const_reference at(const typename object_t::key_type& key) const
2563 {
2564 // at only works for objects
2565 if (m_type != value_t::object)
2566 {
2567 throw std::domain_error("cannot use at() with " + type_name());
2568 }
2569
2570 return m_value.object->at(key);
2571 }
2572
2573 /*!
2574 @brief access specified array element
2575
2576 Returns a reference to the element at specified location @a idx.
2577
2578 @note If @a idx is beyond the range of the array (i.e., `idx >= size()`),
2579 then the array is silently filled up with `null` values to make `idx` a
2580 valid reference to the last stored element.
2581
2582 @param[in] idx index of the element to access
2583
2584 @return reference to the element at index @a idx
2585
2586 @throw std::domain_error if JSON is not an array or null
2587
2588 @complexity Constant if @a idx is in the range of the array. Otherwise
2589 linear in `idx - size()`.
2590
2591 @liveexample{The example below shows how array elements can be read and
2592 written using [] operator. Note the addition of `null`
2593 values.,operatorarray__size_type}
2594 */
2595 reference operator[](size_type idx)
2596 {
2597 // implicitly convert null to object
2598 if (m_type == value_t::null)
2599 {
2600 m_type = value_t::array;
2601 AllocatorType<array_t> alloc;
2602 m_value.array = alloc.allocate(1);
2603 alloc.construct(m_value.array);
2604 }
2605
2606 // [] only works for arrays
2607 if (m_type != value_t::array)
2608 {
2609 throw std::domain_error("cannot use operator[] with " + type_name());
2610 }
2611
2612 for (size_t i = m_value.array->size(); i <= idx; ++i)
2613 {
2614 m_value.array->push_back(basic_json());
2615 }
2616
2617 return m_value.array->operator[](idx);
2618 }
2619
2620 /*!
2621 @brief access specified array element
2622
2623 Returns a const reference to the element at specified location @a idx.
2624
2625 @param[in] idx index of the element to access
2626
2627 @return const reference to the element at index @a idx
2628
2629 @throw std::domain_error if JSON is not an array
2630
2631 @complexity Constant.
2632
2633 @liveexample{The example below shows how array elements can be read using
2634 the [] operator.,operatorarray__size_type_const}
2635 */
2636 const_reference operator[](size_type idx) const
2637 {
2638 // at only works for arrays
2639 if (m_type != value_t::array)
2640 {
2641 throw std::domain_error("cannot use operator[] with " + type_name());
2642 }
2643
2644 return m_value.array->operator[](idx);
2645 }
2646
2647 /*!
2648 @brief access specified object element
2649
2650 Returns a reference to the element at with specified key @a key.
2651
2652 @note If @a key is not found in the object, then it is silently added to
2653 the object and filled with a `null` value to make `key` a valid reference.
2654 In case the value was `null` before, it is converted to an object.
2655
2656 @param[in] key key of the element to access
2657
2658 @return reference to the element at key @a key
2659
2660 @throw std::domain_error if JSON is not an object or null
2661
2662 @complexity Logarithmic in the size of the container.
2663
2664 @liveexample{The example below shows how object elements can be read and
2665 written using the [] operator.,operatorarray__key_type}
2666 */
2667 reference operator[](const typename object_t::key_type& key)
2668 {
2669 // implicitly convert null to object
2670 if (m_type == value_t::null)
2671 {
2672 m_type = value_t::object;
2673 AllocatorType<object_t> alloc;
2674 m_value.object = alloc.allocate(1);
2675 alloc.construct(m_value.object);
2676 }
2677
2678 // [] only works for objects
2679 if (m_type != value_t::object)
2680 {
2681 throw std::domain_error("cannot use operator[] with " + type_name());
2682 }
2683
2684 return m_value.object->operator[](key);
2685 }
2686
2687 /*!
2688 @brief access specified object element
2689
2690 Returns a reference to the element at with specified key @a key.
2691
2692 @param[in] key key of the element to access
2693
2694 @return reference to the element at key @a key
2695
2696 @throw std::domain_error if JSON is not an object or null
2697
2698 @complexity Logarithmic in the size of the container.
2699
2700 @liveexample{The example below shows how object elements can be read using
2701 the [] operator.,operatorarray__key_type_const}
2702 */
2703 const_reference operator[](const typename object_t::key_type& key) const
2704 {
2705 // at only works for objects
2706 if (m_type != value_t::object)
2707 {
2708 throw std::domain_error("cannot use operator[] with " + type_name());
2709 }
2710
2711 return m_value.object->operator[](key);
2712 }
2713
2714 /*!
2715 @brief access specified object element
2716
2717 Returns a reference to the element at with specified key @a key.
2718
2719 @note If @a key is not found in the object, then it is silently added to
2720 the object and filled with a `null` value to make `key` a valid reference.
2721 In case the value was `null` before, it is converted to an object.
2722
2723 @note This function is required for compatibility reasons with Clang.
2724
2725 @param[in] key key of the element to access
2726
2727 @return reference to the element at key @a key
2728
2729 @throw std::domain_error if JSON is not an object or null
2730
2731 @complexity Logarithmic in the size of the container.
2732
2733 @liveexample{The example below shows how object elements can be read and
2734 written using the [] operator.,operatorarray__key_type}
2735 */
2736 template<typename T, std::size_t n>
2737 reference operator[](const T (&key)[n])
2738 {
2739 // implicitly convert null to object
2740 if (m_type == value_t::null)
2741 {
2742 m_type = value_t::object;
2743 m_value = value_t::object;
2744 }
2745
2746 // at only works for objects
2747 if (m_type != value_t::object)
2748 {
2749 throw std::domain_error("cannot use operator[] with " + type_name());
2750 }
2751
2752 return m_value.object->operator[](key);
2753 }
2754
2755 /*!
2756 @brief access specified object element
2757
2758 Returns a reference to the element at with specified key @a key.
2759
2760 @note This function is required for compatibility reasons with Clang.
2761
2762 @param[in] key key of the element to access
2763
2764 @return reference to the element at key @a key
2765
2766 @throw std::domain_error if JSON is not an object or null
2767
2768 @complexity Logarithmic in the size of the container.
2769
2770 @liveexample{The example below shows how object elements can be read using
2771 the [] operator.,operatorarray__key_type_const}
2772 */
2773 template<typename T, std::size_t n>
2774 const_reference operator[](const T (&key)[n]) const
2775 {
2776 // at only works for objects
2777 if (m_type != value_t::object)
2778 {
2779 throw std::domain_error("cannot use operator[] with " + type_name());
2780 }
2781
2782 return m_value.object->operator[](key);
2783 }
2784
2785 /*!
2786 @brief access the first element
2787
2788 Returns a reference to the first element in the container. For a JSON
2789 container `c`, the expression `c.front()` is equivalent to `*c.begin()`.
2790
2791 @return In case of a structured type (array or object), a reference to the
2792 first element is returned. In cast of number, string, or boolean values, a
2793 reference to the value is returned.
2794
2795 @complexity Constant.
2796
2797 @note Calling `front` on an empty container is undefined.
2798
2799 @throw std::out_of_range when called on null value
2800
2801 @liveexample{The following code shows an example for @ref front.,front}
2802 */
2803 reference front()
2804 {
2805 return *begin();
2806 }
2807
2808 /*!
2809 @copydoc basic_json::front()
2810 */
2811 const_reference front() const
2812 {
2813 return *cbegin();
2814 }
2815
2816 /*!
2817 @brief access the last element
2818
2819 Returns a reference to the last element in the container. For a JSON
2820 container `c`, the expression `c.back()` is equivalent to `{ auto tmp =
2821 c.end(); --tmp; return *tmp; }`.
2822
2823 @return In case of a structured type (array or object), a reference to the
2824 last element is returned. In cast of number, string, or boolean values, a
2825 reference to the value is returned.
2826
2827 @complexity Constant.
2828
2829 @note Calling `back` on an empty container is undefined.
2830
2831 @throw std::out_of_range when called on null value.
2832
2833 @liveexample{The following code shows an example for @ref back.,back}
2834 */
2835 reference back()
2836 {
2837 auto tmp = end();
2838 --tmp;
2839 return *tmp;
2840 }
2841
2842 /*!
2843 @copydoc basic_json::back()
2844 */
2845 const_reference back() const
2846 {
2847 auto tmp = cend();
2848 --tmp;
2849 return *tmp;
2850 }
2851
2852 /*!
2853 @brief remove element given an iterator
2854
2855 Removes the element specified by iterator @a pos. Invalidates iterators and
2856 references at or after the point of the erase, including the end()
2857 iterator. The iterator @a pos must be valid and dereferenceable. Thus the
2858 end() iterator (which is valid, but is not dereferencable) cannot be used
2859 as a value for @a pos.
2860
2861 If called on a primitive type other than null, the resulting JSON value
2862 will be `null`.
2863
2864 @param[in] pos iterator to the element to remove
2865 @return Iterator following the last removed element. If the iterator @a pos
2866 refers to the last element, the end() iterator is returned.
2867
2868 @tparam InteratorType an @ref iterator or @ref const_iterator
2869
2870 @throw std::domain_error if called on a `null` value
2871 @throw std::domain_error if called on an iterator which does not belong to
2872 the current JSON value
2873 @throw std::out_of_range if called on a primitive type with invalid iterator
2874 (i.e., any iterator which is not end())
2875
2876 @complexity The complexity depends on the type:
2877 - objects: amortized constant
2878 - arrays: linear in distance between pos and the end of the container
2879 - strings: linear in the length of the string
2880 - other types: constant
2881
2882 @liveexample{The example shows the result of erase for different JSON
2883 types.,erase__IteratorType}
2884 */
2885 template <class InteratorType, typename
2886 std::enable_if<
2887 std::is_same<InteratorType, typename basic_json_t::iterator>::value or
2888 std::is_same<InteratorType, typename basic_json_t::const_iterator>::value
2889 , int>::type
2890 = 0>
2891 InteratorType erase(InteratorType pos)
2892 {
2893 // make sure iterator fits the current value
2894 if (this != pos.m_object)
2895 {
2896 throw std::domain_error("iterator does not fit current value");
2897 }
2898
2899 InteratorType result = end();
2900
2901 switch (m_type)
2902 {
2903 case value_t::number_integer:
2904 case value_t::number_float:
2905 case value_t::boolean:
2906 case value_t::string:
2907 {
2908 if (not pos.m_it.primitive_iterator.is_begin())
2909 {
2910 throw std::out_of_range("iterator out of range");
2911 }
2912
2913 if (m_type == value_t::string)
2914 {
2915 delete m_value.string;
2916 m_value.string = nullptr;
2917 }
2918
2919 m_type = value_t::null;
2920 break;
2921 }
2922
2923 case value_t::object:
2924 {
2925 result.m_it.object_iterator = m_value.object->erase(pos.m_it.object_iterator);
2926 break;
2927 }
2928
2929 case value_t::array:
2930 {
2931 result.m_it.array_iterator = m_value.array->erase(pos.m_it.array_iterator);
2932 break;
2933 }
2934
2935 default:
2936 {
2937 throw std::domain_error("cannot use erase() with " + type_name());
2938 }
2939 }
2940
2941 return result;
2942 }
2943
2944 /*!
2945 @brief remove elements given an iterator range
2946
2947 Removes the element specified by the range `[first; last)`. Invalidates
2948 iterators and references at or after the point of the erase, including the
2949 end() iterator. The iterator @a first does not need to be dereferenceable
2950 if `first == last`: erasing an empty range is a no-op.
2951
2952 If called on a primitive type other than null, the resulting JSON value
2953 will be `null`.
2954
2955 @param[in] first iterator to the beginning of the range to remove
2956 @param[in] last iterator past the end of the range to remove
2957 @return Iterator following the last removed element. If the iterator @a
2958 second refers to the last element, the end() iterator is returned.
2959
2960 @tparam InteratorType an @ref iterator or @ref const_iterator
2961
2962 @throw std::domain_error if called on a `null` value
2963 @throw std::domain_error if called on iterators which does not belong to
2964 the current JSON value
2965 @throw std::out_of_range if called on a primitive type with invalid iterators
2966 (i.e., if `first != begin()` and `last != end()`)
2967
2968 @complexity The complexity depends on the type:
2969 - objects: `log(size()) + std::distance(first, last)`
2970 - arrays: linear in the distance between @a first and @a last, plus linear
2971 in the distance between @a last and end of the container
2972 - strings: linear in the length of the string
2973 - other types: constant
2974
2975 @liveexample{The example shows the result of erase for different JSON
2976 types.,erase__IteratorType_IteratorType}
2977 */
2978 template <class InteratorType, typename
2979 std::enable_if<
2980 std::is_same<InteratorType, typename basic_json_t::iterator>::value or
2981 std::is_same<InteratorType, typename basic_json_t::const_iterator>::value
2982 , int>::type
2983 = 0>
2984 InteratorType erase(InteratorType first, InteratorType last)
2985 {
2986 // make sure iterator fits the current value
2987 if (this != first.m_object or this != last.m_object)
2988 {
2989 throw std::domain_error("iterators do not fit current value");
2990 }
2991
2992 InteratorType result = end();
2993
2994 switch (m_type)
2995 {
2996 case value_t::number_integer:
2997 case value_t::number_float:
2998 case value_t::boolean:
2999 case value_t::string:
3000 {
3001 if (not first.m_it.primitive_iterator.is_begin() or not last.m_it.primitive_iterator.is_end())
3002 {
3003 throw std::out_of_range("iterators out of range");
3004 }
3005
3006 if (m_type == value_t::string)
3007 {
3008 delete m_value.string;
3009 m_value.string = nullptr;
3010 }
3011
3012 m_type = value_t::null;
3013 break;
3014 }
3015
3016 case value_t::object:
3017 {
3018 result.m_it.object_iterator = m_value.object->erase(first.m_it.object_iterator,
3019 last.m_it.object_iterator);
3020 break;
3021 }
3022
3023 case value_t::array:
3024 {
3025 result.m_it.array_iterator = m_value.array->erase(first.m_it.array_iterator,
3026 last.m_it.array_iterator);
3027 break;
3028 }
3029
3030 default:
3031 {
3032 throw std::domain_error("cannot use erase with " + type_name());
3033 }
3034 }
3035
3036 return result;
3037 }
3038
3039 /*!
3040 @brief remove element from a JSON object given a key
3041
3042 Removes elements from a JSON object with the key value @a key.
3043
3044 @param[in] key value of the elements to remove
3045
3046 @return Number of elements removed. If ObjectType is the default `std::map`
3047 type, the return value will always be `0` (@a key was not found) or `1` (@a
3048 key was found).
3049
3050 @throw std::domain_error when called on a type other than JSON object
3051
3052 @complexity `log(size()) + count(key)`
3053
3054 @liveexample{The example shows the effect of erase.,erase__key_type}
3055 */
3056 size_type erase(const typename object_t::key_type& key)
3057 {
3058 // this erase only works for objects
3059 if (m_type != value_t::object)
3060 {
3061 throw std::domain_error("cannot use erase() with " + type_name());
3062 }
3063
3064 return m_value.object->erase(key);
3065 }
3066
3067 /*!
3068 @brief remove element from a JSON array given an index
3069
3070 Removes element from a JSON array at the index @a idx.
3071
3072 @param[in] idx index of the element to remove
3073
3074 @throw std::domain_error when called on a type other than JSON array
3075 @throw std::out_of_range when `idx >= size()`
3076
3077 @complexity Linear in distance between @a idx and the end of the container.
3078
3079 @liveexample{The example shows the effect of erase.,erase__size_type}
3080 */
3081 void erase(const size_type idx)
3082 {
3083 // this erase only works for arrays
3084 if (m_type != value_t::array)
3085 {
3086 throw std::domain_error("cannot use erase() with " + type_name());
3087 }
3088
3089 if (idx >= size())
3090 {
3091 throw std::out_of_range("index out of range");
3092 }
3093
3094 m_value.array->erase(m_value.array->begin() + static_cast<difference_type>(idx));
3095 }
3096
3097 /*!
3098 @brief find an element in a JSON object
3099
3100 Finds an element in a JSON object with key equivalent to @a key. If the
3101 element is not found or the JSON value is not an object, end() is returned.
3102
3103 @param[in] key key value of the element to search for
3104
3105 @return Iterator to an element with key equivalent to @a key. If no such
3106 element is found, past-the-end (see end()) iterator is returned.
3107
3108 @complexity Logarithmic in the size of the JSON object.
3109
3110 @liveexample{The example shows how find is used.,find__key_type}
3111 */
3112 iterator find(typename object_t::key_type key)
3113 {
3114 auto result = end();
3115
3116 if (m_type == value_t::object)
3117 {
3118 result.m_it.object_iterator = m_value.object->find(key);
3119 }
3120
3121 return result;
3122 }
3123
3124 /*!
3125 @brief find an element in a JSON object
3126 @copydoc find(typename object_t::key_type)
3127 */
3128 const_iterator find(typename object_t::key_type key) const
3129 {
3130 auto result = cend();
3131
3132 if (m_type == value_t::object)
3133 {
3134 result.m_it.object_iterator = m_value.object->find(key);
3135 }
3136
3137 return result;
3138 }
3139
3140 /*!
3141 @brief returns the number of occurrences of a key in a JSON object
3142
3143 Returns the number of elements with key @a key. If ObjectType is the
3144 default `std::map` type, the return value will always be `0` (@a key was
3145 not found) or `1` (@a key was found).
3146
3147 @param[in] key key value of the element to count
3148
3149 @return Number of elements with key @a key. If the JSON value is not an
3150 object, the return value will be `0`.
3151
3152 @complexity Logarithmic in the size of the JSON object.
3153
3154 @liveexample{The example shows how count is used.,count}
3155 */
3156 size_type count(typename object_t::key_type key) const
3157 {
3158 // return 0 for all nonobject types
3159 return (m_type == value_t::object) ? m_value.object->count(key) : 0;
3160 }
3161
3162 /// @}
3163
3164
3165 ///////////////
3166 // iterators //
3167 ///////////////
3168
3169 /// @name iterators
3170 /// @{
3171
3172 /*!
3173 @brief returns an iterator to the first element
3174
3175 Returns an iterator to the first element.
3176
3177 @image html range-begin-end.svg "Illustration from cppreference.com"
3178
3179 @return iterator to the first element
3180
3181 @complexity Constant.
3182
3183 @requirement This function satisfies the Container requirements:
3184 - The complexity is constant.
3185
3186 @liveexample{The following code shows an example for @ref begin.,begin}
3187 */
3188 iterator begin()
3189 {
3190 iterator result(this);
3191 result.set_begin();
3192 return result;
3193 }
3194
3195 /*!
3196 @copydoc basic_json::cbegin()
3197 */
3198 const_iterator begin() const
3199 {
3200 return cbegin();
3201 }
3202
3203 /*!
3204 @brief returns a const iterator to the first element
3205
3206 Returns a const iterator to the first element.
3207
3208 @image html range-begin-end.svg "Illustration from cppreference.com"
3209
3210 @return const iterator to the first element
3211
3212 @complexity Constant.
3213
3214 @requirement This function satisfies the Container requirements:
3215 - The complexity is constant.
3216 - Has the semantics of `const_cast<const basic_json&>(*this).begin()`.
3217
3218 @liveexample{The following code shows an example for @ref cbegin.,cbegin}
3219 */
3220 const_iterator cbegin() const
3221 {
3222 const_iterator result(this);
3223 result.set_begin();
3224 return result;
3225 }
3226
3227 /*!
3228 @brief returns an iterator to one past the last element
3229
3230 Returns an iterator to one past the last element.
3231
3232 @image html range-begin-end.svg "Illustration from cppreference.com"
3233
3234 @return iterator one past the last element
3235
3236 @complexity Constant.
3237
3238 @requirement This function satisfies the Container requirements:
3239 - The complexity is constant.
3240
3241 @liveexample{The following code shows an example for @ref end.,end}
3242 */
3243 iterator end()
3244 {
3245 iterator result(this);
3246 result.set_end();
3247 return result;
3248 }
3249
3250 /*!
3251 @copydoc basic_json::cend()
3252 */
3253 const_iterator end() const
3254 {
3255 return cend();
3256 }
3257
3258 /*!
3259 @brief returns a const iterator to one past the last element
3260
3261 Returns a const iterator to one past the last element.
3262
3263 @image html range-begin-end.svg "Illustration from cppreference.com"
3264
3265 @return const iterator one past the last element
3266
3267 @complexity Constant.
3268
3269 @requirement This function satisfies the Container requirements:
3270 - The complexity is constant.
3271 - Has the semantics of `const_cast<const basic_json&>(*this).end()`.
3272
3273 @liveexample{The following code shows an example for @ref cend.,cend}
3274 */
3275 const_iterator cend() const
3276 {
3277 const_iterator result(this);
3278 result.set_end();
3279 return result;
3280 }
3281
3282 /*!
3283 @brief returns an iterator to the reverse-beginning
3284
3285 Returns an iterator to the reverse-beginning; that is, the last element.
3286
3287 @image html range-rbegin-rend.svg "Illustration from cppreference.com"
3288
3289 @complexity Constant.
3290
3291 @requirement This function satisfies the ReversibleContainer requirements:
3292 - The complexity is constant.
3293 - Has the semantics of `reverse_iterator(end())`.
3294
3295 @liveexample{The following code shows an example for @ref rbegin.,rbegin}
3296 */
3297 reverse_iterator rbegin()
3298 {
3299 return reverse_iterator(end());
3300 }
3301
3302 /*!
3303 @copydoc basic_json::crbegin()
3304 */
3305 const_reverse_iterator rbegin() const
3306 {
3307 return crbegin();
3308 }
3309
3310 /*!
3311 @brief returns an iterator to the reverse-end
3312
3313 Returns an iterator to the reverse-end; that is, one before the first
3314 element.
3315
3316 @image html range-rbegin-rend.svg "Illustration from cppreference.com"
3317
3318 @complexity Constant.
3319
3320 @requirement This function satisfies the ReversibleContainer requirements:
3321 - The complexity is constant.
3322 - Has the semantics of `reverse_iterator(begin())`.
3323
3324 @liveexample{The following code shows an example for @ref rend.,rend}
3325 */
3326 reverse_iterator rend()
3327 {
3328 return reverse_iterator(begin());
3329 }
3330
3331 /*!
3332 @copydoc basic_json::crend()
3333 */
3334 const_reverse_iterator rend() const
3335 {
3336 return crend();
3337 }
3338
3339 /*!
3340 @brief returns a const reverse iterator to the last element
3341
3342 Returns a const iterator to the reverse-beginning; that is, the last
3343 element.
3344
3345 @image html range-rbegin-rend.svg "Illustration from cppreference.com"
3346
3347 @complexity Constant.
3348
3349 @requirement This function satisfies the ReversibleContainer requirements:
3350 - The complexity is constant.
3351 - Has the semantics of `const_cast<const basic_json&>(*this).rbegin()`.
3352
3353 @liveexample{The following code shows an example for @ref crbegin.,crbegin}
3354 */
3355 const_reverse_iterator crbegin() const
3356 {
3357 return const_reverse_iterator(cend());
3358 }
3359
3360 /*!
3361 @brief returns a const reverse iterator to one before the first
3362
3363 Returns a const reverse iterator to the reverse-end; that is, one before
3364 the first element.
3365
3366 @image html range-rbegin-rend.svg "Illustration from cppreference.com"
3367
3368 @complexity Constant.
3369
3370 @requirement This function satisfies the ReversibleContainer requirements:
3371 - The complexity is constant.
3372 - Has the semantics of `const_cast<const basic_json&>(*this).rend()`.
3373
3374 @liveexample{The following code shows an example for @ref crend.,crend}
3375 */
3376 const_reverse_iterator crend() const
3377 {
3378 return const_reverse_iterator(cbegin());
3379 }
3380
3381 /// @}
3382
3383
3384 //////////////
3385 // capacity //
3386 //////////////
3387
3388 /// @name capacity
3389 /// @{
3390
3391 /*!
3392 @brief checks whether the container is empty
3393
3394 Checks if a JSON value has no elements.
3395
3396 @return The return value depends on the different types and is
3397 defined as follows:
3398 Value type | return value
3399 ----------- | -------------
3400 null | @c true
3401 boolean | @c false
3402 string | @c false
3403 number | @c false
3404 object | result of function object_t::empty()
3405 array | result of function array_t::empty()
3406
3407 @complexity Constant, as long as @ref array_t and @ref object_t satisfy the
3408 Container concept; that is, their empty() functions have
3409 constant complexity.
3410
3411 @requirement This function satisfies the Container requirements:
3412 - The complexity is constant.
3413 - Has the semantics of `begin() == end()`.
3414
3415 @liveexample{The following code uses @ref empty to check if a @ref json
3416 object contains any elements.,empty}
3417 */
3418 bool empty() const noexcept
3419 {
3420 switch (m_type)
3421 {
3422 case (value_t::null):
3423 {
3424 return true;
3425 }
3426
3427 case (value_t::array):
3428 {
3429 return m_value.array->empty();
3430 }
3431
3432 case (value_t::object):
3433 {
3434 return m_value.object->empty();
3435 }
3436
3437 default:
3438 {
3439 // all other types are nonempty
3440 return false;
3441 }
3442 }
3443 }
3444
3445 /*!
3446 @brief returns the number of elements
3447
3448 Returns the number of elements in a JSON value.
3449
3450 @return The return value depends on the different types and is
3451 defined as follows:
3452 Value type | return value
3453 ----------- | -------------
3454 null | @c 0
3455 boolean | @c 1
3456 string | @c 1
3457 number | @c 1
3458 object | result of function object_t::size()
3459 array | result of function array_t::size()
3460
3461 @complexity Constant, as long as @ref array_t and @ref object_t satisfy the
3462 Container concept; that is, their size() functions have
3463 constant complexity.
3464
3465 @requirement This function satisfies the Container requirements:
3466 - The complexity is constant.
3467 - Has the semantics of `std::distance(begin(), end())`.
3468
3469 @liveexample{The following code calls @ref size on the different value
3470 types.,size}
3471 */
3472 size_type size() const noexcept
3473 {
3474 switch (m_type)
3475 {
3476 case (value_t::null):
3477 {
3478 return 0;
3479 }
3480
3481 case (value_t::array):
3482 {
3483 return m_value.array->size();
3484 }
3485
3486 case (value_t::object):
3487 {
3488 return m_value.object->size();
3489 }
3490
3491 default:
3492 {
3493 // all other types have size 1
3494 return 1;
3495 }
3496 }
3497 }
3498
3499 /*!
3500 @brief returns the maximum possible number of elements
3501
3502 Returns the maximum number of elements a JSON value is able to hold due to
3503 system or library implementation limitations, i.e. `std::distance(begin(),
3504 end())` for the JSON value.
3505
3506 @return The return value depends on the different types and is
3507 defined as follows:
3508 Value type | return value
3509 ----------- | -------------
3510 null | @c 0 (same as size())
3511 boolean | @c 1 (same as size())
3512 string | @c 1 (same as size())
3513 number | @c 1 (same as size())
3514 object | result of function object_t::max_size()
3515 array | result of function array_t::max_size()
3516
3517 @complexity Constant, as long as @ref array_t and @ref object_t satisfy the
3518 Container concept; that is, their max_size() functions have
3519 constant complexity.
3520
3521 @requirement This function satisfies the Container requirements:
3522 - The complexity is constant.
3523 - Has the semantics of returning `b.size()` where `b` is the largest
3524 possible JSON value.
3525
3526 @liveexample{The following code calls @ref max_size on the different value
3527 types. Note the output is implementation specific.,max_size}
3528 */
3529 size_type max_size() const noexcept
3530 {
3531 switch (m_type)
3532 {
3533 case (value_t::array):
3534 {
3535 return m_value.array->max_size();
3536 }
3537
3538 case (value_t::object):
3539 {
3540 return m_value.object->max_size();
3541 }
3542
3543 default:
3544 {
3545 // all other types have max_size() == size()
3546 return size();
3547 }
3548 }
3549 }
3550
3551 /// @}
3552
3553
3554 ///////////////
3555 // modifiers //
3556 ///////////////
3557
3558 /// @name modifiers
3559 /// @{
3560
3561 /*!
3562 @brief clears the contents
3563
3564 Clears the content of a JSON value and resets it to the default value as
3565 if @ref basic_json(value_t) would have been called:
3566
3567 Value type | initial value
3568 ----------- | -------------
3569 null | `null`
3570 boolean | `false`
3571 string | `""`
3572 number | `0`
3573 object | `{}`
3574 array | `[]`
3575
3576 @note Floating-point numbers are set to `0.0` which will be serialized to
3577 `0`. The vale type remains @ref number_float_t.
3578
3579 @complexity Linear in the size of the JSON value.
3580
3581 @liveexample{The example below shows the effect of @ref clear to different
3582 JSON types.,clear}
3583 */
3584 void clear() noexcept
3585 {
3586 switch (m_type)
3587 {
3588 case (value_t::null):
3589 case (value_t::discarded):
3590 {
3591 break;
3592 }
3593
3594 case (value_t::number_integer):
3595 {
3596 m_value.number_integer = 0;
3597 break;
3598 }
3599
3600 case (value_t::number_float):
3601 {
3602 m_value.number_float = 0.0;
3603 break;
3604 }
3605
3606 case (value_t::boolean):
3607 {
3608 m_value.boolean = false;
3609 break;
3610 }
3611
3612 case (value_t::string):
3613 {
3614 m_value.string->clear();
3615 break;
3616 }
3617
3618 case (value_t::array):
3619 {
3620 m_value.array->clear();
3621 break;
3622 }
3623
3624 case (value_t::object):
3625 {
3626 m_value.object->clear();
3627 break;
3628 }
3629 }
3630 }
3631
3632 /*!
3633 @brief add an object to an array
3634
3635 Appends the given element @a value to the end of the JSON value. If the
3636 function is called on a JSON null value, an empty array is created before
3637 appending @a value.
3638
3639 @param value the value to add to the JSON array
3640
3641 @throw std::domain_error when called on a type other than JSON array or null
3642
3643 @complexity Amortized constant.
3644
3645 @liveexample{The example shows how `push_back` and `+=` can be used to add
3646 elements to a JSON array. Note how the `null` value was silently converted
3647 to a JSON array.,push_back}
3648 */
3649 void push_back(basic_json&& value)
3650 {
3651 // push_back only works for null objects or arrays
3652 if (not(m_type == value_t::null or m_type == value_t::array))
3653 {
3654 throw std::domain_error("cannot use push_back() with " + type_name());
3655 }
3656
3657 // transform null object into an array
3658 if (m_type == value_t::null)
3659 {
3660 m_type = value_t::array;
3661 m_value = value_t::array;
3662 }
3663
3664 // add element to array (move semantics)
3665 m_value.array->push_back(std::move(value));
3666 // invalidate object
3667 value.m_type = value_t::null;
3668 }
3669
3670 /*!
3671 @brief add an object to an array
3672 @copydoc push_back(basic_json&&)
3673 */
3674 reference operator+=(basic_json&& value)
3675 {
3676 push_back(std::move(value));
3677 return *this;
3678 }
3679
3680 /*!
3681 @brief add an object to an array
3682 @copydoc push_back(basic_json&&)
3683 */
3684 void push_back(const basic_json& value)
3685 {
3686 // push_back only works for null objects or arrays
3687 if (not(m_type == value_t::null or m_type == value_t::array))
3688 {
3689 throw std::domain_error("cannot use push_back() with " + type_name());
3690 }
3691
3692 // transform null object into an array
3693 if (m_type == value_t::null)
3694 {
3695 m_type = value_t::array;
3696 m_value = value_t::array;
3697 }
3698
3699 // add element to array
3700 m_value.array->push_back(value);
3701 }
3702
3703 /*!
3704 @brief add an object to an array
3705 @copydoc push_back(basic_json&&)
3706 */
3707 reference operator+=(const basic_json& value)
3708 {
3709 push_back(value);
3710 return *this;
3711 }
3712
3713 /*!
3714 @brief add an object to an object
3715
3716 Inserts the given element @a value to the JSON object. If the function is
3717 called on a JSON null value, an empty object is created before inserting @a
3718 value.
3719
3720 @param[in] value the value to add to the JSON object
3721
3722 @throw std::domain_error when called on a type other than JSON object or
3723 null
3724
3725 @complexity Logarithmic in the size of the container, O(log(`size()`)).
3726
3727 @liveexample{The example shows how `push_back` and `+=` can be used to add
3728 elements to a JSON object. Note how the `null` value was silently converted
3729 to a JSON object.,push_back__object_t__value}
3730 */
3731 void push_back(const typename object_t::value_type& value)
3732 {
3733 // push_back only works for null objects or objects
3734 if (not(m_type == value_t::null or m_type == value_t::object))
3735 {
3736 throw std::domain_error("cannot use push_back() with " + type_name());
3737 }
3738
3739 // transform null object into an object
3740 if (m_type == value_t::null)
3741 {
3742 m_type = value_t::object;
3743 m_value = value_t::object;
3744 }
3745
3746 // add element to array
3747 m_value.object->insert(value);
3748 }
3749
3750 /*!
3751 @brief add an object to an object
3752 @copydoc push_back(const typename object_t::value_type&)
3753 */
3754 reference operator+=(const typename object_t::value_type& value)
3755 {
3756 push_back(value);
3757 return operator[](value.first);
3758 }
3759
3760 /*!
3761 @brief inserts element
3762
3763 Inserts element @a value before iterator @a pos.
3764
3765 @param[in] pos iterator before which the content will be inserted; may be
3766 the end() iterator
3767 @param[in] value element to insert
3768 @return iterator pointing to the inserted @a value.
3769
3770 @throw std::domain_error if called on JSON values other than arrays
3771 @throw std::domain_error if @a pos is not an iterator of *this
3772
3773 @complexity Constant plus linear in the distance between pos and end of the
3774 container.
3775
3776 @liveexample{The example shows how insert is used.,insert}
3777 */
3778 iterator insert(const_iterator pos, const basic_json& value)
3779 {
3780 // insert only works for arrays
3781 if (m_type != value_t::array)
3782 {
3783 throw std::domain_error("cannot use insert() with " + type_name());
3784 }
3785
3786 // check if iterator pos fits to this JSON value
3787 if (pos.m_object != this)
3788 {
3789 throw std::domain_error("iterator does not fit current value");
3790 }
3791
3792 // insert to array and return iterator
3793 iterator result(this);
3794 result.m_it.array_iterator = m_value.array->insert(pos.m_it.array_iterator, value);
3795 return result;
3796 }
3797
3798 /*!
3799 @brief inserts element
3800 @copydoc insert(const_iterator, const basic_json&)
3801 */
3802 iterator insert(const_iterator pos, basic_json&& value)
3803 {
3804 return insert(pos, value);
3805 }
3806
3807 /*!
3808 @brief inserts elements
3809
3810 Inserts @a count copies of @a value before iterator @a pos.
3811
3812 @param[in] pos iterator before which the content will be inserted; may be
3813 the end() iterator
3814 @param[in] count number of copies of @a value to insert
3815 @param[in] value element to insert
3816 @return iterator pointing to the first element inserted, or @a pos if
3817 `count==0`
3818
3819 @throw std::domain_error if called on JSON values other than arrays
3820 @throw std::domain_error if @a pos is not an iterator of *this
3821
3822 @complexity Linear in @a count plus linear in the distance between @a pos
3823 and end of the container.
3824
3825 @liveexample{The example shows how insert is used.,insert__count}
3826 */
3827 iterator insert(const_iterator pos, size_type count, const basic_json& value)
3828 {
3829 // insert only works for arrays
3830 if (m_type != value_t::array)
3831 {
3832 throw std::domain_error("cannot use insert() with " + type_name());
3833 }
3834
3835 // check if iterator pos fits to this JSON value
3836 if (pos.m_object != this)
3837 {
3838 throw std::domain_error("iterator does not fit current value");
3839 }
3840
3841 // insert to array and return iterator
3842 iterator result(this);
3843 result.m_it.array_iterator = m_value.array->insert(pos.m_it.array_iterator, count, value);
3844 return result;
3845 }
3846
3847 /*!
3848 @brief inserts elements
3849
3850 Inserts elements from range `[first, last)` before iterator @a pos.
3851
3852 @param[in] pos iterator before which the content will be inserted; may be
3853 the end() iterator
3854 @param[in] first begin of the range of elements to insert
3855 @param[in] last end of the range of elements to insert
3856
3857 @throw std::domain_error if called on JSON values other than arrays
3858 @throw std::domain_error if @a pos is not an iterator of *this
3859 @throw std::domain_error if @a first and @a last do not belong to the same
3860 JSON value
3861 @throw std::domain_error if @a first or @a last are iterators into
3862 container for which insert is called
3863 @return iterator pointing to the first element inserted, or @a pos if
3864 `first==last`
3865
3866 @complexity Linear in `std::distance(first, last)` plus linear in the
3867 distance between @a pos and end of the container.
3868
3869 @liveexample{The example shows how insert is used.,insert__range}
3870 */
3871 iterator insert(const_iterator pos, const_iterator first, const_iterator last)
3872 {
3873 // insert only works for arrays
3874 if (m_type != value_t::array)
3875 {
3876 throw std::domain_error("cannot use insert() with " + type_name());
3877 }
3878
3879 // check if iterator pos fits to this JSON value
3880 if (pos.m_object != this)
3881 {
3882 throw std::domain_error("iterator does not fit current value");
3883 }
3884
3885 if (first.m_object != last.m_object)
3886 {
3887 throw std::domain_error("iterators does not fit");
3888 }
3889
3890 if (first.m_object == this or last.m_object == this)
3891 {
3892 throw std::domain_error("passed iterators may not belong to container");
3893 }
3894
3895 // insert to array and return iterator
3896 iterator result(this);
3897 result.m_it.array_iterator = m_value.array->insert(pos.m_it.array_iterator,
3898 first.m_it.array_iterator, last.m_it.array_iterator);
3899 return result;
3900 }
3901
3902 /*!
3903 @brief inserts elements
3904
3905 Inserts elements from initializer list @a ilist before iterator @a pos.
3906
3907 @param[in] pos iterator before which the content will be inserted; may be
3908 the end() iterator
3909 @param[in] ilist initializer list to insert the values from
3910
3911 @throw std::domain_error if called on JSON values other than arrays
3912 @throw std::domain_error if @a pos is not an iterator of *this
3913 @return iterator pointing to the first element inserted, or @a pos if
3914 `ilist` is empty
3915
3916 @complexity Linear in `ilist.size()` plus linear in the distance between @a
3917 pos and end of the container.
3918
3919 @liveexample{The example shows how insert is used.,insert__ilist}
3920 */
3921 iterator insert(const_iterator pos, std::initializer_list<basic_json> ilist)
3922 {
3923 // insert only works for arrays
3924 if (m_type != value_t::array)
3925 {
3926 throw std::domain_error("cannot use insert() with " + type_name());
3927 }
3928
3929 // check if iterator pos fits to this JSON value
3930 if (pos.m_object != this)
3931 {
3932 throw std::domain_error("iterator does not fit current value");
3933 }
3934
3935 // insert to array and return iterator
3936 iterator result(this);
3937 result.m_it.array_iterator = m_value.array->insert(pos.m_it.array_iterator, ilist);
3938 return result;
3939 }
3940
3941 /*!
3942 @brief exchanges the values
3943
3944 Exchanges the contents of the JSON value with those of @a other. Does not
3945 invoke any move, copy, or swap operations on individual elements. All
3946 iterators and references remain valid. The past-the-end iterator is
3947 invalidated.
3948
3949 @param[in,out] other JSON value to exchange the contents with
3950
3951 @complexity Constant.
3952
3953 @liveexample{The example below shows how JSON arrays can be
3954 swapped.,swap__reference}
3955 */
3956 void swap(reference other) noexcept (
3957 std::is_nothrow_move_constructible<value_t>::value and
3958 std::is_nothrow_move_assignable<value_t>::value and
3959 std::is_nothrow_move_constructible<json_value>::value and
3960 std::is_nothrow_move_assignable<json_value>::value
3961 )
3962 {
3963 std::swap(m_type, other.m_type);
3964 std::swap(m_value, other.m_value);
3965 }
3966
3967 /*!
3968 @brief exchanges the values
3969
3970 Exchanges the contents of a JSON array with those of @a other. Does not
3971 invoke any move, copy, or swap operations on individual elements. All
3972 iterators and references remain valid. The past-the-end iterator is
3973 invalidated.
3974
3975 @param[in,out] other array to exchange the contents with
3976
3977 @throw std::domain_error when JSON value is not an array
3978
3979 @complexity Constant.
3980
3981 @liveexample{The example below shows how JSON values can be
3982 swapped.,swap__array_t}
3983 */
3984 void swap(array_t& other)
3985 {
3986 // swap only works for arrays
3987 if (m_type != value_t::array)
3988 {
3989 throw std::domain_error("cannot use swap() with " + type_name());
3990 }
3991
3992 // swap arrays
3993 std::swap(*(m_value.array), other);
3994 }
3995
3996 /*!
3997 @brief exchanges the values
3998
3999 Exchanges the contents of a JSON object with those of @a other. Does not
4000 invoke any move, copy, or swap operations on individual elements. All
4001 iterators and references remain valid. The past-the-end iterator is
4002 invalidated.
4003
4004 @param[in,out] other object to exchange the contents with
4005
4006 @throw std::domain_error when JSON value is not an object
4007
4008 @complexity Constant.
4009
4010 @liveexample{The example below shows how JSON values can be
4011 swapped.,swap__object_t}
4012 */
4013 void swap(object_t& other)
4014 {
4015 // swap only works for objects
4016 if (m_type != value_t::object)
4017 {
4018 throw std::domain_error("cannot use swap() with " + type_name());
4019 }
4020
4021 // swap objects
4022 std::swap(*(m_value.object), other);
4023 }
4024
4025 /*!
4026 @brief exchanges the values
4027
4028 Exchanges the contents of a JSON string with those of @a other. Does not
4029 invoke any move, copy, or swap operations on individual elements. All
4030 iterators and references remain valid. The past-the-end iterator is
4031 invalidated.
4032
4033 @param[in,out] other string to exchange the contents with
4034
4035 @throw std::domain_error when JSON value is not a string
4036
4037 @complexity Constant.
4038
4039 @liveexample{The example below shows how JSON values can be
4040 swapped.,swap__string_t}
4041 */
4042 void swap(string_t& other)
4043 {
4044 // swap only works for strings
4045 if (m_type != value_t::string)
4046 {
4047 throw std::domain_error("cannot use swap() with " + type_name());
4048 }
4049
4050 // swap strings
4051 std::swap(*(m_value.string), other);
4052 }
4053
4054 /// @}
4055
4056
4057 //////////////////////////////////////////
4058 // lexicographical comparison operators //
4059 //////////////////////////////////////////
4060
4061 /// @name lexicographical comparison operators
4062 /// @{
4063
4064 private:
4065 /*!
4066 @brief comparison operator for JSON types
4067
4068 Returns an ordering that is similar to Python:
4069 - order: null < boolean < number < object < array < string
4070 - furthermore, each type is not smaller than itself
4071 */
4072 friend bool operator<(const value_t lhs, const value_t rhs)
4073 {
4074 static constexpr std::array<uint8_t, 7> order = {{
4075 0, // null
4076 3, // object
4077 4, // array
4078 5, // string
4079 1, // boolean
4080 2, // integer
4081 2 // float
4082 }
4083 };
4084
4085 // discarded values are not comparable
4086 if (lhs == value_t::discarded or rhs == value_t::discarded)
4087 {
4088 return false;
4089 }
4090
4091 return order[static_cast<std::size_t>(lhs)] < order[static_cast<std::size_t>(rhs)];
4092 }
4093
4094 public:
4095 /*!
4096 @brief comparison: equal
4097
4098 Compares two JSON values for equality according to the following rules:
4099 - Two JSON values are equal if (1) they are from the same type and (2)
4100 their stored values are the same.
4101 - Integer and floating-point numbers are automatically converted before
4102 comparison. Floating-point numbers are compared indirectly: two
4103 floating-point numbers `f1` and `f2` are considered equal if neither
4104 `f1 > f2` nor `f2 > f1` holds.
4105 - Two JSON null values are equal.
4106
4107 @param[in] lhs first JSON value to consider
4108 @param[in] rhs second JSON value to consider
4109 @return whether the values @a lhs and @a rhs are equal
4110
4111 @complexity Linear.
4112
4113 @liveexample{The example demonstrates comparing several JSON
4114 types.,operator__equal}
4115 */
4116 friend bool operator==(const_reference lhs, const_reference rhs) noexcept
4117 {
4118 const auto lhs_type = lhs.type();
4119 const auto rhs_type = rhs.type();
4120
4121 if (lhs_type == rhs_type)
4122 {
4123 switch (lhs_type)
4124 {
4125 case (value_t::array):
4126 return *lhs.m_value.array == *rhs.m_value.array;
4127 case (value_t::object):
4128 return *lhs.m_value.object == *rhs.m_value.object;
4129 case (value_t::null):
4130 return true;
4131 case (value_t::string):
4132 return *lhs.m_value.string == *rhs.m_value.string;
4133 case (value_t::boolean):
4134 return lhs.m_value.boolean == rhs.m_value.boolean;
4135 case (value_t::number_integer):
4136 return lhs.m_value.number_integer == rhs.m_value.number_integer;
4137 case (value_t::number_float):
4138 return approx(lhs.m_value.number_float, rhs.m_value.number_float);
4139 case (value_t::discarded):
4140 return false;
4141 }
4142 }
4143 else if (lhs_type == value_t::number_integer and rhs_type == value_t::number_float)
4144 {
4145 return approx(static_cast<number_float_t>(lhs.m_value.number_integer),
4146 rhs.m_value.number_float);
4147 }
4148 else if (lhs_type == value_t::number_float and rhs_type == value_t::number_integer)
4149 {
4150 return approx(lhs.m_value.number_float,
4151 static_cast<number_float_t>(rhs.m_value.number_integer));
4152 }
4153 return false;
4154 }
4155
4156 /*!
4157 @brief comparison: equal
4158
4159 The functions compares the given JSON value against a null pointer. As the
4160 null pointer can be used to initialize a JSON value to null, a comparison
4161 of JSON value @a v with a null pointer should be equivalent to call
4162 `v.is_null()`.
4163
4164 @param[in] v JSON value to consider
4165 @return whether @a v is null
4166
4167 @complexity Constant.
4168
4169 @liveexample{The example compares several JSON types to the null pointer.
4170 ,operator__equal__nullptr_t}
4171 */
4172 friend bool operator==(const_reference v, std::nullptr_t) noexcept
4173 {
4174 return v.is_null();
4175 }
4176
4177 /*!
4178 @brief comparison: equal
4179 @copydoc operator==(const_reference, std::nullptr_t)
4180 */
4181 friend bool operator==(std::nullptr_t, const_reference v) noexcept
4182 {
4183 return v.is_null();
4184 }
4185
4186 /*!
4187 @brief comparison: not equal
4188
4189 Compares two JSON values for inequality by calculating `not (lhs == rhs)`.
4190
4191 @param[in] lhs first JSON value to consider
4192 @param[in] rhs second JSON value to consider
4193 @return whether the values @a lhs and @a rhs are not equal
4194
4195 @complexity Linear.
4196
4197 @liveexample{The example demonstrates comparing several JSON
4198 types.,operator__notequal}
4199 */
4200 friend bool operator!=(const_reference lhs, const_reference rhs) noexcept
4201 {
4202 return not (lhs == rhs);
4203 }
4204
4205 /*!
4206 @brief comparison: not equal
4207
4208 The functions compares the given JSON value against a null pointer. As the
4209 null pointer can be used to initialize a JSON value to null, a comparison
4210 of JSON value @a v with a null pointer should be equivalent to call
4211 `not v.is_null()`.
4212
4213 @param[in] v JSON value to consider
4214 @return whether @a v is not null
4215
4216 @complexity Constant.
4217
4218 @liveexample{The example compares several JSON types to the null pointer.
4219 ,operator__notequal__nullptr_t}
4220 */
4221 friend bool operator!=(const_reference v, std::nullptr_t) noexcept
4222 {
4223 return not v.is_null();
4224 }
4225
4226 /*!
4227 @brief comparison: not equal
4228 @copydoc operator!=(const_reference, std::nullptr_t)
4229 */
4230 friend bool operator!=(std::nullptr_t, const_reference v) noexcept
4231 {
4232 return not v.is_null();
4233 }
4234
4235 /*!
4236 @brief comparison: less than
4237
4238 Compares whether one JSON value @a lhs is less than another JSON value @a
4239 rhs according to the following rules:
4240 - If @a lhs and @a rhs have the same type, the values are compared using
4241 the default `<` operator.
4242 - Integer and floating-point numbers are automatically converted before
4243 comparison
4244 - In case @a lhs and @a rhs have different types, the values are ignored
4245 and the order of the types is considered, see
4246 @ref operator<(const value_t, const value_t).
4247
4248 @param[in] lhs first JSON value to consider
4249 @param[in] rhs second JSON value to consider
4250 @return whether @a lhs is less than @a rhs
4251
4252 @complexity Linear.
4253
4254 @liveexample{The example demonstrates comparing several JSON
4255 types.,operator__less}
4256 */
4257 friend bool operator<(const_reference lhs, const_reference rhs) noexcept
4258 {
4259 const auto lhs_type = lhs.type();
4260 const auto rhs_type = rhs.type();
4261
4262 if (lhs_type == rhs_type)
4263 {
4264 switch (lhs_type)
4265 {
4266 case (value_t::array):
4267 return *lhs.m_value.array < *rhs.m_value.array;
4268 case (value_t::object):
4269 return *lhs.m_value.object < *rhs.m_value.object;
4270 case (value_t::null):
4271 return false;
4272 case (value_t::string):
4273 return *lhs.m_value.string < *rhs.m_value.string;
4274 case (value_t::boolean):
4275 return lhs.m_value.boolean < rhs.m_value.boolean;
4276 case (value_t::number_integer):
4277 return lhs.m_value.number_integer < rhs.m_value.number_integer;
4278 case (value_t::number_float):
4279 return lhs.m_value.number_float < rhs.m_value.number_float;
4280 case (value_t::discarded):
4281 return false;
4282 }
4283 }
4284 else if (lhs_type == value_t::number_integer and rhs_type == value_t::number_float)
4285 {
4286 return static_cast<number_float_t>(lhs.m_value.number_integer) <
4287 rhs.m_value.number_float;
4288 }
4289 else if (lhs_type == value_t::number_float and rhs_type == value_t::number_integer)
4290 {
4291 return lhs.m_value.number_float <
4292 static_cast<number_float_t>(rhs.m_value.number_integer);
4293 }
4294
4295 // We only reach this line if we cannot compare values. In that case,
4296 // we compare types. Note we have to call the operator explicitly,
4297 // because MSVC has problems otherwise.
4298 return operator<(lhs_type, rhs_type);
4299 }
4300
4301 /*!
4302 @brief comparison: less than or equal
4303
4304 Compares whether one JSON value @a lhs is less than or equal to another
4305 JSON value by calculating `not (rhs < lhs)`.
4306
4307 @param[in] lhs first JSON value to consider
4308 @param[in] rhs second JSON value to consider
4309 @return whether @a lhs is less than or equal to @a rhs
4310
4311 @complexity Linear.
4312
4313 @liveexample{The example demonstrates comparing several JSON
4314 types.,operator__greater}
4315 */
4316 friend bool operator<=(const_reference lhs, const_reference rhs) noexcept
4317 {
4318 return not (rhs < lhs);
4319 }
4320
4321 /*!
4322 @brief comparison: greater than
4323
4324 Compares whether one JSON value @a lhs is greater than another
4325 JSON value by calculating `not (lhs <= rhs)`.
4326
4327 @param[in] lhs first JSON value to consider
4328 @param[in] rhs second JSON value to consider
4329 @return whether @a lhs is greater than to @a rhs
4330
4331 @complexity Linear.
4332
4333 @liveexample{The example demonstrates comparing several JSON
4334 types.,operator__lessequal}
4335 */
4336 friend bool operator>(const_reference lhs, const_reference rhs) noexcept
4337 {
4338 return not (lhs <= rhs);
4339 }
4340
4341 /*!
4342 @brief comparison: greater than or equal
4343
4344 Compares whether one JSON value @a lhs is greater than or equal to another
4345 JSON value by calculating `not (lhs < rhs)`.
4346
4347 @param[in] lhs first JSON value to consider
4348 @param[in] rhs second JSON value to consider
4349 @return whether @a lhs is greater than or equal to @a rhs
4350
4351 @complexity Linear.
4352
4353 @liveexample{The example demonstrates comparing several JSON
4354 types.,operator__greaterequal}
4355 */
4356 friend bool operator>=(const_reference lhs, const_reference rhs) noexcept
4357 {
4358 return not (lhs < rhs);
4359 }
4360
4361 /// @}
4362
4363
4364 ///////////////////
4365 // serialization //
4366 ///////////////////
4367
4368 /// @name serialization
4369 /// @{
4370
4371 /*!
4372 @brief serialize to stream
4373
4374 Serialize the given JSON value @a j to the output stream @a o. The JSON
4375 value will be serialized using the @ref dump member function. The
4376 indentation of the output can be controlled with the member variable
4377 `width` of the output stream @a o. For instance, using the manipulator
4378 `std::setw(4)` on @a o sets the indentation level to `4` and the
4379 serialization result is the same as calling `dump(4)`.
4380
4381 @param[in,out] o stream to serialize to
4382 @param[in] j JSON value to serialize
4383
4384 @return the stream @a o
4385
4386 @complexity Linear.
4387
4388 @liveexample{The example below shows the serialization with different
4389 parameters to `width` to adjust the indentation level.,operator_serialize}
4390 */
4391 friend std::ostream& operator<<(std::ostream& o, const basic_json& j)
4392 {
4393 // read width member and use it as indentation parameter if nonzero
4394 const bool pretty_print = (o.width() > 0);
4395 const auto indentation = (pretty_print ? o.width() : 0);
4396
4397 // reset width to 0 for subsequent calls to this stream
4398 o.width(0);
4399
4400 // do the actual serialization
4401 j.dump(o, pretty_print, static_cast<unsigned int>(indentation));
4402 return o;
4403 }
4404
4405 /*!
4406 @brief serialize to stream
4407 @copydoc operator<<(std::ostream&, const basic_json&)
4408 */
4409 friend std::ostream& operator>>(const basic_json& j, std::ostream& o)
4410 {
4411 return o << j;
4412 }
4413
4414 /// @}
4415
4416
4417 /////////////////////
4418 // deserialization //
4419 /////////////////////
4420
4421 /// @name deserialization
4422 /// @{
4423
4424 /*!
4425 @brief deserialize from string
4426
4427 @param[in] s string to read a serialized JSON value from
4428 @param[in] cb a parser callback function of type @ref parser_callback_t
4429 which is used to control the deserialization by filtering unwanted values
4430 (optional)
4431
4432 @return result of the deserialization
4433
4434 @complexity Linear in the length of the input. The parser is a predictive
4435 LL(1) parser. The complexity can be higher if the parser callback function
4436 @a cb has a super-linear complexity.
4437
4438 @liveexample{The example below demonstrates the parse function with and
4439 without callback function.,parse__string__parser_callback_t}
4440
4441 @sa parse(std::istream&, parser_callback_t) for a version that reads from
4442 an input stream
4443 */
4444 static basic_json parse(const string_t& s, parser_callback_t cb = nullptr)
4445 {
4446 return parser(s, cb).parse();
4447 }
4448
4449 /*!
4450 @brief deserialize from stream
4451
4452 @param[in,out] i stream to read a serialized JSON value from
4453 @param[in] cb a parser callback function of type @ref parser_callback_t
4454 which is used to control the deserialization by filtering unwanted values
4455 (optional)
4456
4457 @return result of the deserialization
4458
4459 @complexity Linear in the length of the input. The parser is a predictive
4460 LL(1) parser. The complexity can be higher if the parser callback function
4461 @a cb has a super-linear complexity.
4462
4463 @liveexample{The example below demonstrates the parse function with and
4464 without callback function.,parse__istream__parser_callback_t}
4465
4466 @sa parse(const string_t&, parser_callback_t) for a version that reads
4467 from a string
4468 */
4469 static basic_json parse(std::istream& i, parser_callback_t cb = nullptr)
4470 {
4471 return parser(i, cb).parse();
4472 }
4473
4474 /*!
4475 @brief deserialize from stream
4476
4477 Deserializes an input stream to a JSON value.
4478
4479 @param[in,out] i input stream to read a serialized JSON value from
4480 @param[in,out] j JSON value to write the deserialized input to
4481
4482 @throw std::invalid_argument in case of parse errors
4483
4484 @complexity Linear in the length of the input. The parser is a predictive
4485 LL(1) parser.
4486
4487 @liveexample{The example below shows how a JSON value is constructed by
4488 reading a serialization from a stream.,operator_deserialize}
4489
4490 @sa parse(std::istream&, parser_callback_t) for a variant with a parser
4491 callback function to filter values while parsing
4492 */
4493 friend std::istream& operator<<(basic_json& j, std::istream& i)
4494 {
4495 j = parser(i).parse();
4496 return i;
4497 }
4498
4499 /*!
4500 @brief deserialize from stream
4501 @copydoc operator<<(basic_json&, std::istream&)
4502 */
4503 friend std::istream& operator>>(std::istream& i, basic_json& j)
4504 {
4505 j = parser(i).parse();
4506 return i;
4507 }
4508
4509 /// @}
4510
4511
4512 private:
4513 ///////////////////////////
4514 // convenience functions //
4515 ///////////////////////////
4516
4517 /// return the type as string
4518 string_t type_name() const
4519 {
4520 switch (m_type)
4521 {
4522 case (value_t::null):
4523 {
4524 return "null";
4525 }
4526
4527 case (value_t::object):
4528 {
4529 return "object";
4530 }
4531
4532 case (value_t::array):
4533 {
4534 return "array";
4535 }
4536
4537 case (value_t::string):
4538 {
4539 return "string";
4540 }
4541
4542 case (value_t::boolean):
4543 {
4544 return "boolean";
4545 }
4546
4547 case (value_t::discarded):
4548 {
4549 return "discarded";
4550 }
4551
4552 default:
4553 {
4554 return "number";
4555 }
4556 }
4557 }
4558
4559 /*!
4560 @brief calculates the extra space to escape a JSON string
4561
4562 @param[in] s the string to escape
4563 @return the number of characters required to escape string @a s
4564
4565 @complexity Linear in the length of string @a s.
4566 */
4567 static std::size_t extra_space(const string_t& s) noexcept
4568 {
4569 std::size_t result = 0;
4570
4571 for (const auto& c : s)
4572 {
4573 switch (c)
4574 {
4575 case '"':
4576 case '\\':
4577 case '\b':
4578 case '\f':
4579 case '\n':
4580 case '\r':
4581 case '\t':
4582 {
4583 // from c (1 byte) to \x (2 bytes)
4584 result += 1;
4585 break;
4586 }
4587
4588 default:
4589 {
4590 if (c >= 0x00 and c <= 0x1f)
4591 {
4592 // from c (1 byte) to \uxxxx (6 bytes)
4593 result += 5;
4594 }
4595 break;
4596 }
4597 }
4598 }
4599
4600 return result;
4601 }
4602
4603 /*!
4604 @brief escape a string
4605
4606 Escape a string by replacing certain special characters by a sequence of an
4607 escape character (backslash) and another character and other control
4608 characters by a sequence of "\u" followed by a four-digit hex
4609 representation.
4610
4611 @param[in] s the string to escape
4612 @return the escaped string
4613
4614 @complexity Linear in the length of string @a s.
4615 */
4616 static string_t escape_string(const string_t& s) noexcept
4617 {
4618 const auto space = extra_space(s);
4619 if (space == 0)
4620 {
4621 return s;
4622 }
4623
4624 // create a result string of necessary size
4625 string_t result(s.size() + space, '\\');
4626 std::size_t pos = 0;
4627
4628 for (const auto& c : s)
4629 {
4630 switch (c)
4631 {
4632 // quotation mark (0x22)
4633 case '"':
4634 {
4635 result[pos + 1] = '"';
4636 pos += 2;
4637 break;
4638 }
4639
4640 // reverse solidus (0x5c)
4641 case '\\':
4642 {
4643 // nothing to change
4644 pos += 2;
4645 break;
4646 }
4647
4648 // backspace (0x08)
4649 case '\b':
4650 {
4651 result[pos + 1] = 'b';
4652 pos += 2;
4653 break;
4654 }
4655
4656 // formfeed (0x0c)
4657 case '\f':
4658 {
4659 result[pos + 1] = 'f';
4660 pos += 2;
4661 break;
4662 }
4663
4664 // newline (0x0a)
4665 case '\n':
4666 {
4667 result[pos + 1] = 'n';
4668 pos += 2;
4669 break;
4670 }
4671
4672 // carriage return (0x0d)
4673 case '\r':
4674 {
4675 result[pos + 1] = 'r';
4676 pos += 2;
4677 break;
4678 }
4679
4680 // horizontal tab (0x09)
4681 case '\t':
4682 {
4683 result[pos + 1] = 't';
4684 pos += 2;
4685 break;
4686 }
4687
4688 default:
4689 {
4690 if (c >= 0x00 and c <= 0x1f)
4691 {
4692 // print character c as \uxxxx
4693 sprintf(&result[pos + 1], "u%04x", int(c));
4694 pos += 6;
4695 // overwrite trailing null character
4696 result[pos] = '\\';
4697 }
4698 else
4699 {
4700 // all other characters are added as-is
4701 result[pos++] = c;
4702 }
4703 break;
4704 }
4705 }
4706 }
4707
4708 return result;
4709 }
4710
4711 /*!
4712 @brief internal implementation of the serialization function
4713
4714 This function is called by the public member function dump and organizes
4715 the serializaion internally. The indentation level is propagated as
4716 additional parameter. In case of arrays and objects, the function is called
4717 recursively. Note that
4718
4719 - strings and object keys are escaped using escape_string()
4720 - integer numbers are converted implictly via operator<<
4721 - floating-point numbers are converted to a string using "%g" format
4722
4723 @param[out] o stream to write to
4724 @param[in] pretty_print whether the output shall be pretty-printed
4725 @param[in] indent_step the indent level
4726 @param[in] current_indent the current indent level (only used internally)
4727 */
4728 void dump(std::ostream& o, const bool pretty_print, const unsigned int indent_step,
4729 const unsigned int current_indent = 0) const
4730 {
4731 // variable to hold indentation for recursive calls
4732 unsigned int new_indent = current_indent;
4733
4734 switch (m_type)
4735 {
4736 case (value_t::object):
4737 {
4738 if (m_value.object->empty())
4739 {
4740 o << "{}";
4741 return;
4742 }
4743
4744 o << "{";
4745
4746 // increase indentation
4747 if (pretty_print)
4748 {
4749 new_indent += indent_step;
4750 o << "\n";
4751 }
4752
4753 for (auto i = m_value.object->cbegin(); i != m_value.object->cend(); ++i)
4754 {
4755 if (i != m_value.object->cbegin())
4756 {
4757 o << (pretty_print ? ",\n" : ",");
4758 }
4759 o << string_t(new_indent, ' ') << "\""
4760 << escape_string(i->first) << "\":"
4761 << (pretty_print ? " " : "");
4762 i->second.dump(o, pretty_print, indent_step, new_indent);
4763 }
4764
4765 // decrease indentation
4766 if (pretty_print)
4767 {
4768 new_indent -= indent_step;
4769 o << "\n";
4770 }
4771
4772 o << string_t(new_indent, ' ') + "}";
4773 return;
4774 }
4775
4776 case (value_t::array):
4777 {
4778 if (m_value.array->empty())
4779 {
4780 o << "[]";
4781 return;
4782 }
4783
4784 o << "[";
4785
4786 // increase indentation
4787 if (pretty_print)
4788 {
4789 new_indent += indent_step;
4790 o << "\n";
4791 }
4792
4793 for (auto i = m_value.array->cbegin(); i != m_value.array->cend(); ++i)
4794 {
4795 if (i != m_value.array->cbegin())
4796 {
4797 o << (pretty_print ? ",\n" : ",");
4798 }
4799 o << string_t(new_indent, ' ');
4800 i->dump(o, pretty_print, indent_step, new_indent);
4801 }
4802
4803 // decrease indentation
4804 if (pretty_print)
4805 {
4806 new_indent -= indent_step;
4807 o << "\n";
4808 }
4809
4810 o << string_t(new_indent, ' ') << "]";
4811 return;
4812 }
4813
4814 case (value_t::string):
4815 {
4816 o << string_t("\"") << escape_string(*m_value.string) << "\"";
4817 return;
4818 }
4819
4820 case (value_t::boolean):
4821 {
4822 o << (m_value.boolean ? "true" : "false");
4823 return;
4824 }
4825
4826 case (value_t::number_integer):
4827 {
4828 o << m_value.number_integer;
4829 return;
4830 }
4831
4832 case (value_t::number_float):
4833 {
4834 // 15 digits of precision allows round-trip IEEE 754
4835 // string->double->string; to be safe, we read this value from
4836 // std::numeric_limits<number_float_t>::digits10
4837 o << std::setprecision(std::numeric_limits<number_float_t>::digits10) << m_value.number_float;
4838 return;
4839 }
4840
4841 case (value_t::discarded):
4842 {
4843 o << "<discarded>";
4844 return;
4845 }
4846
4847 default:
4848 {
4849 o << "null";
4850 return;
4851 }
4852 }
4853 }
4854
4855 private:
4856 //////////////////////
4857 // member variables //
4858 //////////////////////
4859
4860 /// the type of the current element
4861 value_t m_type = value_t::null;
4862
4863 /// the value of the current element
4864 json_value m_value = {};
4865
4866
4867 private:
4868 ///////////////
4869 // iterators //
4870 ///////////////
4871
4872 /*!
4873 @brief an iterator for primitive JSON types
4874
4875 This class models an iterator for primitive JSON types (boolean, number,
4876 string). It's only purpose is to allow the iterator/const_iterator classes
4877 to "iterate" over primitive values. Internally, the iterator is modeled by
4878 a `difference_type` variable. Value begin_value (`0`) models the begin,
4879 end_value (`1`) models past the end.
4880 */
4881 class primitive_iterator_t
4882 {
4883 public:
4884 /// set iterator to a defined beginning
4885 void set_begin()
4886 {
4887 m_it = begin_value;
4888 }
4889
4890 /// set iterator to a defined past the end
4891 void set_end()
4892 {
4893 m_it = end_value;
4894 }
4895
4896 /// return whether the iterator can be dereferenced
4897 bool is_begin() const
4898 {
4899 return (m_it == begin_value);
4900 }
4901
4902 /// return whether the iterator is at end
4903 bool is_end() const
4904 {
4905 return (m_it == end_value);
4906 }
4907
4908 /// return reference to the value to change and compare
4909 operator difference_type& ()
4910 {
4911 return m_it;
4912 }
4913
4914 /// return value to compare
4915 operator difference_type () const
4916 {
4917 return m_it;
4918 }
4919
4920 private:
4921 static constexpr difference_type begin_value = 0;
4922 static constexpr difference_type end_value = begin_value + 1;
4923
4924 /// iterator as signed integer type
4925 difference_type m_it = std::numeric_limits<std::ptrdiff_t>::min();
4926 };
4927
4928 /*!
4929 @brief an iterator value
4930
4931 @note This structure could easily be a union, but MSVC currently does not
4932 allow unions members with complex constructors, see
4933 https://github.com/nlohmann/json/pull/105.
4934 */
4935 struct internal_iterator
4936 {
4937 /// iterator for JSON objects
4938 typename object_t::iterator object_iterator;
4939 /// iterator for JSON arrays
4940 typename array_t::iterator array_iterator;
4941 /// generic iterator for all other types
4942 primitive_iterator_t primitive_iterator;
4943
4944 /// create an uninitialized internal_iterator
4945 internal_iterator()
4946 : object_iterator(), array_iterator(), primitive_iterator()
4947 {}
4948 };
4949
4950 public:
4951 /*!
4952 @brief a const random access iterator for the @ref basic_json class
4953
4954 This class implements a const iterator for the @ref basic_json class. From
4955 this class, the @ref iterator class is derived.
4956
4957 @requirement The class satisfies the following concept requirements:
4958 - [RandomAccessIterator](http://en.cppreference.com/w/cpp/concept/RandomAccessIterator):
4959 The iterator that can be moved to point (forward and backward) to any
4960 element in constant time.
4961 */
4962 class const_iterator : public std::iterator<std::random_access_iterator_tag, const basic_json>
4963 {
4964 /// allow basic_json to access private members
4965 friend class basic_json;
4966
4967 public:
4968 /// the type of the values when the iterator is dereferenced
4969 using value_type = typename basic_json::value_type;
4970 /// a type to represent differences between iterators
4971 using difference_type = typename basic_json::difference_type;
4972 /// defines a pointer to the type iterated over (value_type)
4973 using pointer = typename basic_json::const_pointer;
4974 /// defines a reference to the type iterated over (value_type)
4975 using reference = typename basic_json::const_reference;
4976 /// the category of the iterator
4977 using iterator_category = std::bidirectional_iterator_tag;
4978
4979 /// default constructor
4980 const_iterator() = default;
4981
4982 /// constructor for a given JSON instance
4983 const_iterator(pointer object) : m_object(object)
4984 {
4985 switch (m_object->m_type)
4986 {
4987 case (basic_json::value_t::object):
4988 {
4989 m_it.object_iterator = typename object_t::iterator();
4990 break;
4991 }
4992 case (basic_json::value_t::array):
4993 {
4994 m_it.array_iterator = typename array_t::iterator();
4995 break;
4996 }
4997 default:
4998 {
4999 m_it.primitive_iterator = primitive_iterator_t();
5000 break;
5001 }
5002 }
5003 }
5004
5005 /// copy constructor given a nonconst iterator
5006 const_iterator(const iterator& other) : m_object(other.m_object)
5007 {
5008 switch (m_object->m_type)
5009 {
5010 case (basic_json::value_t::object):
5011 {
5012 m_it.object_iterator = other.m_it.object_iterator;
5013 break;
5014 }
5015
5016 case (basic_json::value_t::array):
5017 {
5018 m_it.array_iterator = other.m_it.array_iterator;
5019 break;
5020 }
5021
5022 default:
5023 {
5024 m_it.primitive_iterator = other.m_it.primitive_iterator;
5025 break;
5026 }
5027 }
5028 }
5029
5030 /// copy constructor
5031 const_iterator(const const_iterator& other) noexcept
5032 : m_object(other.m_object), m_it(other.m_it)
5033 {}
5034
5035 /// copy assignment
5036 const_iterator& operator=(const_iterator other) noexcept(
5037 std::is_nothrow_move_constructible<pointer>::value and
5038 std::is_nothrow_move_assignable<pointer>::value and
5039 std::is_nothrow_move_constructible<internal_iterator>::value and
5040 std::is_nothrow_move_assignable<internal_iterator>::value
5041 )
5042 {
5043 std::swap(m_object, other.m_object);
5044 std::swap(m_it, other.m_it);
5045 return *this;
5046 }
5047
5048 private:
5049 /// set the iterator to the first value
5050 void set_begin()
5051 {
5052 switch (m_object->m_type)
5053 {
5054 case (basic_json::value_t::object):
5055 {
5056 m_it.object_iterator = m_object->m_value.object->begin();
5057 break;
5058 }
5059
5060 case (basic_json::value_t::array):
5061 {
5062 m_it.array_iterator = m_object->m_value.array->begin();
5063 break;
5064 }
5065
5066 case (basic_json::value_t::null):
5067 {
5068 // set to end so begin()==end() is true: null is empty
5069 m_it.primitive_iterator.set_end();
5070 break;
5071 }
5072
5073 default:
5074 {
5075 m_it.primitive_iterator.set_begin();
5076 break;
5077 }
5078 }
5079 }
5080
5081 /// set the iterator past the last value
5082 void set_end()
5083 {
5084 switch (m_object->m_type)
5085 {
5086 case (basic_json::value_t::object):
5087 {
5088 m_it.object_iterator = m_object->m_value.object->end();
5089 break;
5090 }
5091
5092 case (basic_json::value_t::array):
5093 {
5094 m_it.array_iterator = m_object->m_value.array->end();
5095 break;
5096 }
5097
5098 default:
5099 {
5100 m_it.primitive_iterator.set_end();
5101 break;
5102 }
5103 }
5104 }
5105
5106 public:
5107 /// return a reference to the value pointed to by the iterator
5108 reference operator*() const
5109 {
5110 switch (m_object->m_type)
5111 {
5112 case (basic_json::value_t::object):
5113 {
5114 return m_it.object_iterator->second;
5115 }
5116
5117 case (basic_json::value_t::array):
5118 {
5119 return *m_it.array_iterator;
5120 }
5121
5122 case (basic_json::value_t::null):
5123 {
5124 throw std::out_of_range("cannot get value");
5125 }
5126
5127 default:
5128 {
5129 if (m_it.primitive_iterator.is_begin())
5130 {
5131 return *m_object;
5132 }
5133 else
5134 {
5135 throw std::out_of_range("cannot get value");
5136 }
5137 }
5138 }
5139 }
5140
5141 /// dereference the iterator
5142 pointer operator->() const
5143 {
5144 switch (m_object->m_type)
5145 {
5146 case (basic_json::value_t::object):
5147 {
5148 return &(m_it.object_iterator->second);
5149 }
5150
5151 case (basic_json::value_t::array):
5152 {
5153 return &*m_it.array_iterator;
5154 }
5155
5156 default:
5157 {
5158 if (m_it.primitive_iterator.is_begin())
5159 {
5160 return m_object;
5161 }
5162 else
5163 {
5164 throw std::out_of_range("cannot get value");
5165 }
5166 }
5167 }
5168 }
5169
5170 /// post-increment (it++)
5171 const_iterator operator++(int)
5172 {
5173 auto result = *this;
5174 ++(*this);
5175
5176 return result;
5177 }
5178
5179 /// pre-increment (++it)
5180 const_iterator& operator++()
5181 {
5182 switch (m_object->m_type)
5183 {
5184 case (basic_json::value_t::object):
5185 {
5186 ++m_it.object_iterator;
5187 break;
5188 }
5189
5190 case (basic_json::value_t::array):
5191 {
5192 ++m_it.array_iterator;
5193 break;
5194 }
5195
5196 default:
5197 {
5198 ++m_it.primitive_iterator;
5199 break;
5200 }
5201 }
5202
5203 return *this;
5204 }
5205
5206 /// post-decrement (it--)
5207 const_iterator operator--(int)
5208 {
5209 auto result = *this;
5210 --(*this);
5211
5212 return result;
5213 }
5214
5215 /// pre-decrement (--it)
5216 const_iterator& operator--()
5217 {
5218 switch (m_object->m_type)
5219 {
5220 case (basic_json::value_t::object):
5221 {
5222 --m_it.object_iterator;
5223 break;
5224 }
5225
5226 case (basic_json::value_t::array):
5227 {
5228 --m_it.array_iterator;
5229 break;
5230 }
5231
5232 default:
5233 {
5234 --m_it.primitive_iterator;
5235 break;
5236 }
5237 }
5238
5239 return *this;
5240 }
5241
5242 /// comparison: equal
5243 bool operator==(const const_iterator& other) const
5244 {
5245 // if objects are not the same, the comparison is undefined
5246 if (m_object != other.m_object)
5247 {
5248 throw std::domain_error("cannot compare iterators of different containers");
5249 }
5250
5251 switch (m_object->m_type)
5252 {
5253 case (basic_json::value_t::object):
5254 {
5255 return (m_it.object_iterator == other.m_it.object_iterator);
5256 }
5257
5258 case (basic_json::value_t::array):
5259 {
5260 return (m_it.array_iterator == other.m_it.array_iterator);
5261 }
5262
5263 default:
5264 {
5265 return (m_it.primitive_iterator == other.m_it.primitive_iterator);
5266 }
5267 }
5268 }
5269
5270 /// comparison: not equal
5271 bool operator!=(const const_iterator& other) const
5272 {
5273 return not operator==(other);
5274 }
5275
5276 /// comparison: smaller
5277 bool operator<(const const_iterator& other) const
5278 {
5279 // if objects are not the same, the comparison is undefined
5280 if (m_object != other.m_object)
5281 {
5282 throw std::domain_error("cannot compare iterators of different containers");
5283 }
5284
5285 switch (m_object->m_type)
5286 {
5287 case (basic_json::value_t::object):
5288 {
5289 throw std::domain_error("cannot use operator< for object iterators");
5290 }
5291
5292 case (basic_json::value_t::array):
5293 {
5294 return (m_it.array_iterator < other.m_it.array_iterator);
5295 }
5296
5297 default:
5298 {
5299 return (m_it.primitive_iterator < other.m_it.primitive_iterator);
5300 }
5301 }
5302 }
5303
5304 /// comparison: less than or equal
5305 bool operator<=(const const_iterator& other) const
5306 {
5307 return not other.operator < (*this);
5308 }
5309
5310 /// comparison: greater than
5311 bool operator>(const const_iterator& other) const
5312 {
5313 return not operator<=(other);
5314 }
5315
5316 /// comparison: greater than or equal
5317 bool operator>=(const const_iterator& other) const
5318 {
5319 return not operator<(other);
5320 }
5321
5322 /// add to iterator
5323 const_iterator& operator+=(difference_type i)
5324 {
5325 switch (m_object->m_type)
5326 {
5327 case (basic_json::value_t::object):
5328 {
5329 throw std::domain_error("cannot use operator+= for object iterators");
5330 }
5331
5332 case (basic_json::value_t::array):
5333 {
5334 m_it.array_iterator += i;
5335 break;
5336 }
5337
5338 default:
5339 {
5340 m_it.primitive_iterator += i;
5341 break;
5342 }
5343 }
5344
5345 return *this;
5346 }
5347
5348 /// subtract from iterator
5349 const_iterator& operator-=(difference_type i)
5350 {
5351 return operator+=(-i);
5352 }
5353
5354 /// add to iterator
5355 const_iterator operator+(difference_type i)
5356 {
5357 auto result = *this;
5358 result += i;
5359 return result;
5360 }
5361
5362 /// subtract from iterator
5363 const_iterator operator-(difference_type i)
5364 {
5365 auto result = *this;
5366 result -= i;
5367 return result;
5368 }
5369
5370 /// return difference
5371 difference_type operator-(const const_iterator& other) const
5372 {
5373 switch (m_object->m_type)
5374 {
5375 case (basic_json::value_t::object):
5376 {
5377 throw std::domain_error("cannot use operator- for object iterators");
5378 }
5379
5380 case (basic_json::value_t::array):
5381 {
5382 return m_it.array_iterator - other.m_it.array_iterator;
5383 }
5384
5385 default:
5386 {
5387 return m_it.primitive_iterator - other.m_it.primitive_iterator;
5388 }
5389 }
5390 }
5391
5392 /// access to successor
5393 reference operator[](difference_type n) const
5394 {
5395 switch (m_object->m_type)
5396 {
5397 case (basic_json::value_t::object):
5398 {
5399 throw std::domain_error("cannot use operator[] for object iterators");
5400 }
5401
5402 case (basic_json::value_t::array):
5403 {
5404 return *(m_it.array_iterator + n);
5405 }
5406
5407 case (basic_json::value_t::null):
5408 {
5409 throw std::out_of_range("cannot get value");
5410 }
5411
5412 default:
5413 {
5414 if (m_it.primitive_iterator == -n)
5415 {
5416 return *m_object;
5417 }
5418 else
5419 {
5420 throw std::out_of_range("cannot get value");
5421 }
5422 }
5423 }
5424 }
5425
5426 /// return the key of an object iterator
5427 typename object_t::key_type key() const
5428 {
5429 switch (m_object->m_type)
5430 {
5431 case (basic_json::value_t::object):
5432 {
5433 return m_it.object_iterator->first;
5434 }
5435
5436 default:
5437 {
5438 throw std::domain_error("cannot use key() for non-object iterators");
5439 }
5440 }
5441 }
5442
5443 /// return the value of an iterator
5444 reference value() const
5445 {
5446 return operator*();
5447 }
5448
5449 private:
5450 /// associated JSON instance
5451 pointer m_object = nullptr;
5452 /// the actual iterator of the associated instance
5453 internal_iterator m_it = internal_iterator();
5454 };
5455
5456 /*!
5457 @brief a mutable random access iterator for the @ref basic_json class
5458
5459 @requirement The class satisfies the following concept requirements:
5460 - [RandomAccessIterator](http://en.cppreference.com/w/cpp/concept/RandomAccessIterator):
5461 The iterator that can be moved to point (forward and backward) to any
5462 element in constant time.
5463 - [OutputIterator](http://en.cppreference.com/w/cpp/concept/OutputIterator):
5464 It is possible to write to the pointed-to element.
5465 */
5466 class iterator : public const_iterator
5467 {
5468 public:
5469 using base_iterator = const_iterator;
5470 using pointer = typename basic_json::pointer;
5471 using reference = typename basic_json::reference;
5472
5473 /// default constructor
5474 iterator() = default;
5475
5476 /// constructor for a given JSON instance
5477 iterator(pointer object) noexcept : base_iterator(object)
5478 {}
5479
5480 /// copy constructor
5481 iterator(const iterator& other) noexcept
5482 : base_iterator(other)
5483 {}
5484
5485 /// copy assignment
5486 iterator& operator=(iterator other) noexcept(
5487 std::is_nothrow_move_constructible<pointer>::value and
5488 std::is_nothrow_move_assignable<pointer>::value and
5489 std::is_nothrow_move_constructible<internal_iterator>::value and
5490 std::is_nothrow_move_assignable<internal_iterator>::value
5491 )
5492 {
5493 base_iterator::operator=(other);
5494 return *this;
5495 }
5496
5497 /// return a reference to the value pointed to by the iterator
5498 reference operator*()
5499 {
5500 return const_cast<reference>(base_iterator::operator*());
5501 }
5502
5503 /// dereference the iterator
5504 pointer operator->()
5505 {
5506 return const_cast<pointer>(base_iterator::operator->());
5507 }
5508
5509 /// post-increment (it++)
5510 iterator operator++(int)
5511 {
5512 iterator result = *this;
5513 base_iterator::operator++();
5514 return result;
5515 }
5516
5517 /// pre-increment (++it)
5518 iterator& operator++()
5519 {
5520 base_iterator::operator++();
5521 return *this;
5522 }
5523
5524 /// post-decrement (it--)
5525 iterator operator--(int)
5526 {
5527 iterator result = *this;
5528 base_iterator::operator--();
5529 return result;
5530 }
5531
5532 /// pre-decrement (--it)
5533 iterator& operator--()
5534 {
5535 base_iterator::operator--();
5536 return *this;
5537 }
5538
5539 /// add to iterator
5540 iterator& operator+=(difference_type i)
5541 {
5542 base_iterator::operator+=(i);
5543 return *this;
5544 }
5545
5546 /// subtract from iterator
5547 iterator& operator-=(difference_type i)
5548 {
5549 base_iterator::operator-=(i);
5550 return *this;
5551 }
5552
5553 /// add to iterator
5554 iterator operator+(difference_type i)
5555 {
5556 auto result = *this;
5557 result += i;
5558 return result;
5559 }
5560
5561 /// subtract from iterator
5562 iterator operator-(difference_type i)
5563 {
5564 auto result = *this;
5565 result -= i;
5566 return result;
5567 }
5568
5569 difference_type operator-(const iterator& other) const
5570 {
5571 return base_iterator::operator-(other);
5572 }
5573
5574 /// access to successor
5575 reference operator[](difference_type n) const
5576 {
5577 return const_cast<reference>(base_iterator::operator[](n));
5578 }
5579
5580 /// return the value of an iterator
5581 reference value() const
5582 {
5583 return const_cast<reference>(base_iterator::value());
5584 }
5585 };
5586
5587 /*!
5588 @brief a template for a reverse iterator class
5589
5590 @tparam Base the base iterator type to reverse. Valid types are @ref
5591 iterator (to create @ref reverse_iterator) and @ref const_iterator (to
5592 create @ref const_reverse_iterator).
5593
5594 @requirement The class satisfies the following concept requirements:
5595 - [RandomAccessIterator](http://en.cppreference.com/w/cpp/concept/RandomAccessIterator):
5596 The iterator that can be moved to point (forward and backward) to any
5597 element in constant time.
5598 - [OutputIterator](http://en.cppreference.com/w/cpp/concept/OutputIterator):
5599 It is possible to write to the pointed-to element (only if @a Base is
5600 @ref iterator).
5601 */
5602 template<typename Base>
5603 class json_reverse_iterator : public std::reverse_iterator<Base>
5604 {
5605 public:
5606 /// shortcut to the reverse iterator adaptor
5607 using base_iterator = std::reverse_iterator<Base>;
5608 /// the reference type for the pointed-to element
5609 using reference = typename Base::reference;
5610
5611 /// create reverse iterator from iterator
5612 json_reverse_iterator(const typename base_iterator::iterator_type& it)
5613 : base_iterator(it) {}
5614
5615 /// create reverse iterator from base class
5616 json_reverse_iterator(const base_iterator& it) : base_iterator(it) {}
5617
5618 /// post-increment (it++)
5619 json_reverse_iterator operator++(int)
5620 {
5621 return base_iterator::operator++(1);
5622 }
5623
5624 /// pre-increment (++it)
5625 json_reverse_iterator& operator++()
5626 {
5627 base_iterator::operator++();
5628 return *this;
5629 }
5630
5631 /// post-decrement (it--)
5632 json_reverse_iterator operator--(int)
5633 {
5634 return base_iterator::operator--(1);
5635 }
5636
5637 /// pre-decrement (--it)
5638 json_reverse_iterator& operator--()
5639 {
5640 base_iterator::operator--();
5641 return *this;
5642 }
5643
5644 /// add to iterator
5645 json_reverse_iterator& operator+=(difference_type i)
5646 {
5647 base_iterator::operator+=(i);
5648 return *this;
5649 }
5650
5651 /// add to iterator
5652 json_reverse_iterator operator+(difference_type i) const
5653 {
5654 auto result = *this;
5655 result += i;
5656 return result;
5657 }
5658
5659 /// subtract from iterator
5660 json_reverse_iterator operator-(difference_type i) const
5661 {
5662 auto result = *this;
5663 result -= i;
5664 return result;
5665 }
5666
5667 /// return difference
5668 difference_type operator-(const json_reverse_iterator& other) const
5669 {
5670 return this->base() - other.base();
5671 }
5672
5673 /// access to successor
5674 reference operator[](difference_type n) const
5675 {
5676 return *(this->operator+(n));
5677 }
5678
5679 /// return the key of an object iterator
5680 typename object_t::key_type key() const
5681 {
5682 auto it = --this->base();
5683 return it.key();
5684 }
5685
5686 /// return the value of an iterator
5687 reference value() const
5688 {
5689 auto it = --this->base();
5690 return it.operator * ();
5691 }
5692 };
5693
5694 /*!
5695 @brief wrapper to access iterator member functions in range-based for
5696
5697 This class allows to access @ref key() and @ref value() during range-based
5698 for loops. In these loops, a reference to the JSON values is returned, so
5699 there is no access to the underlying iterator.
5700 */
5701 class iterator_wrapper
5702 {
5703 private:
5704 /// the container to iterate
5705 basic_json& container;
5706 /// the type of the iterator to use while iteration
5707 using json_iterator = decltype(std::begin(container));
5708
5709 /// internal iterator wrapper
5710 class iterator_wrapper_internal
5711 {
5712 private:
5713 /// the iterator
5714 json_iterator anchor;
5715 /// an index for arrays
5716 size_t array_index = 0;
5717
5718 public:
5719 /// construct wrapper given an iterator
5720 iterator_wrapper_internal(json_iterator i) : anchor(i)
5721 {}
5722
5723 /// dereference operator (needed for range-based for)
5724 iterator_wrapper_internal& operator*()
5725 {
5726 return *this;
5727 }
5728
5729 /// increment operator (needed for range-based for)
5730 iterator_wrapper_internal& operator++()
5731 {
5732 ++anchor;
5733 ++array_index;
5734
5735 return *this;
5736 }
5737
5738 /// inequality operator (needed for range-based for)
5739 bool operator!= (const iterator_wrapper_internal& o)
5740 {
5741 return anchor != o.anchor;
5742 }
5743
5744 /// stream operator
5745 friend std::ostream& operator<<(std::ostream& o, const iterator_wrapper_internal& w)
5746 {
5747 return o << w.value();
5748 }
5749
5750 /// return key of the iterator
5751 typename basic_json::string_t key() const
5752 {
5753 switch (anchor.m_object->type())
5754 {
5755 /// use integer array index as key
5756 case (value_t::array):
5757 {
5758 return std::to_string(array_index);
5759 }
5760
5761 /// use key from the object
5762 case (value_t::object):
5763 {
5764 return anchor.key();
5765 }
5766
5767 /// use an empty key for all primitive types
5768 default:
5769 {
5770 return "";
5771 }
5772 }
5773 }
5774
5775 /// return value of the iterator
5776 typename json_iterator::reference value() const
5777 {
5778 return anchor.value();
5779 }
5780 };
5781
5782 public:
5783 /// construct iterator wrapper from a container
5784 iterator_wrapper(basic_json& cont)
5785 : container(cont)
5786 {}
5787
5788 /// return iterator begin (needed for range-based for)
5789 iterator_wrapper_internal begin()
5790 {
5791 return iterator_wrapper_internal(container.begin());
5792 }
5793
5794 /// return iterator end (needed for range-based for)
5795 iterator_wrapper_internal end()
5796 {
5797 return iterator_wrapper_internal(container.end());
5798 }
5799 };
5800
5801 private:
5802 //////////////////////
5803 // lexer and parser //
5804 //////////////////////
5805
5806 /*!
5807 @brief lexical analysis
5808
5809 This class organizes the lexical analysis during JSON deserialization. The
5810 core of it is a scanner generated by re2c <http://re2c.org> that processes
5811 a buffer and recognizes tokens according to RFC 7159.
5812 */
5813 class lexer
5814 {
5815 public:
5816 /// token types for the parser
5817 enum class token_type
5818 {
5819 uninitialized, ///< indicating the scanner is uninitialized
5820 literal_true, ///< the "true" literal
5821 literal_false, ///< the "false" literal
5822 literal_null, ///< the "null" literal
5823 value_string, ///< a string - use get_string() for actual value
5824 value_number, ///< a number - use get_number() for actual value
5825 begin_array, ///< the character for array begin "["
5826 begin_object, ///< the character for object begin "{"
5827 end_array, ///< the character for array end "]"
5828 end_object, ///< the character for object end "}"
5829 name_separator, ///< the name separator ":"
5830 value_separator, ///< the value separator ","
5831 parse_error, ///< indicating a parse error
5832 end_of_input ///< indicating the end of the input buffer
5833 };
5834
5835 /// the char type to use in the lexer
5836 using lexer_char_t = unsigned char;
5837
5838 /// constructor with a given buffer
5839 explicit lexer(const string_t& s) noexcept
5840 : m_stream(nullptr), m_buffer(s)
5841 {
5842 m_content = reinterpret_cast<const lexer_char_t*>(s.c_str());
5843 m_start = m_cursor = m_content;
5844 m_limit = m_content + s.size();
5845 }
5846 explicit lexer(std::istream* s) noexcept
5847 : m_stream(s), m_buffer()
5848 {
5849 getline(*m_stream, m_buffer);
5850 m_content = reinterpret_cast<const lexer_char_t*>(m_buffer.c_str());
5851 m_start = m_cursor = m_content;
5852 m_limit = m_content + m_buffer.size();
5853 }
5854
5855 /// default constructor
5856 lexer() = default;
5857
5858 // switch of unwanted functions
5859 lexer(const lexer&) = delete;
5860 lexer operator=(const lexer&) = delete;
5861
5862 /*!
5863 @brief create a string from a Unicode code point
5864
5865 @param[in] codepoint1 the code point (can be high surrogate)
5866 @param[in] codepoint2 the code point (can be low surrogate or 0)
5867 @return string representation of the code point
5868 @throw std::out_of_range if code point is >0x10ffff
5869 @throw std::invalid_argument if the low surrogate is invalid
5870
5871 @see <http://en.wikipedia.org/wiki/UTF-8#Sample_code>
5872 */
5873 static string_t to_unicode(const std::size_t codepoint1,
5874 const std::size_t codepoint2 = 0)
5875 {
5876 string_t result;
5877
5878 // calculate the codepoint from the given code points
5879 std::size_t codepoint = codepoint1;
5880
5881 // check if codepoint1 is a high surrogate
5882 if (codepoint1 >= 0xD800 and codepoint1 <= 0xDBFF)
5883 {
5884 // check if codepoint2 is a low surrogate
5885 if (codepoint2 >= 0xDC00 and codepoint2 <= 0xDFFF)
5886 {
5887 codepoint =
5888 // high surrogate occupies the most significant 22 bits
5889 (codepoint1 << 10)
5890 // low surrogate occupies the least significant 15 bits
5891 + codepoint2
5892 // there is still the 0xD800, 0xDC00 and 0x10000 noise
5893 // in the result so we have to substract with:
5894 // (0xD800 << 10) + DC00 - 0x10000 = 0x35FDC00
5895 - 0x35FDC00;
5896 }
5897 else
5898 {
5899 throw std::invalid_argument("missing or wrong low surrogate");
5900 }
5901 }
5902
5903 if (codepoint < 0x80)
5904 {
5905 // 1-byte characters: 0xxxxxxx (ASCII)
5906 result.append(1, static_cast<typename string_t::value_type>(codepoint));
5907 }
5908 else if (codepoint <= 0x7ff)
5909 {
5910 // 2-byte characters: 110xxxxx 10xxxxxx
5911 result.append(1, static_cast<typename string_t::value_type>(0xC0 | ((codepoint >> 6) & 0x1F)));
5912 result.append(1, static_cast<typename string_t::value_type>(0x80 | (codepoint & 0x3F)));
5913 }
5914 else if (codepoint <= 0xffff)
5915 {
5916 // 3-byte characters: 1110xxxx 10xxxxxx 10xxxxxx
5917 result.append(1, static_cast<typename string_t::value_type>(0xE0 | ((codepoint >> 12) & 0x0F)));
5918 result.append(1, static_cast<typename string_t::value_type>(0x80 | ((codepoint >> 6) & 0x3F)));
5919 result.append(1, static_cast<typename string_t::value_type>(0x80 | (codepoint & 0x3F)));
5920 }
5921 else if (codepoint <= 0x10ffff)
5922 {
5923 // 4-byte characters: 11110xxx 10xxxxxx 10xxxxxx 10xxxxxx
5924 result.append(1, static_cast<typename string_t::value_type>(0xF0 | ((codepoint >> 18) & 0x07)));
5925 result.append(1, static_cast<typename string_t::value_type>(0x80 | ((codepoint >> 12) & 0x3F)));
5926 result.append(1, static_cast<typename string_t::value_type>(0x80 | ((codepoint >> 6) & 0x3F)));
5927 result.append(1, static_cast<typename string_t::value_type>(0x80 | (codepoint & 0x3F)));
5928 }
5929 else
5930 {
5931 throw std::out_of_range("code points above 0x10FFFF are invalid");
5932 }
5933
5934 return result;
5935 }
5936
5937 /// return name of values of type token_type
5938 static std::string token_type_name(token_type t)
5939 {
5940 switch (t)
5941 {
5942 case (token_type::uninitialized):
5943 return "<uninitialized>";
5944 case (token_type::literal_true):
5945 return "true literal";
5946 case (token_type::literal_false):
5947 return "false literal";
5948 case (token_type::literal_null):
5949 return "null literal";
5950 case (token_type::value_string):
5951 return "string literal";
5952 case (token_type::value_number):
5953 return "number literal";
5954 case (token_type::begin_array):
5955 return "[";
5956 case (token_type::begin_object):
5957 return "{";
5958 case (token_type::end_array):
5959 return "]";
5960 case (token_type::end_object):
5961 return "}";
5962 case (token_type::name_separator):
5963 return ":";
5964 case (token_type::value_separator):
5965 return ",";
5966 case (token_type::end_of_input):
5967 return "<end of input>";
5968 default:
5969 return "<parse error>";
5970 }
5971 }
5972
5973 /*!
5974 This function implements a scanner for JSON. It is specified using
5975 regular expressions that try to follow RFC 7159 as close as possible.
5976 These regular expressions are then translated into a deterministic
5977 finite automaton (DFA) by the tool re2c <http://re2c.org>. As a result,
5978 the translated code for this function consists of a large block of code
5979 with goto jumps.
5980
5981 @return the class of the next token read from the buffer
5982 */
5983 token_type scan() noexcept
5984 {
5985 // pointer for backtracking information
5986 m_marker = nullptr;
5987
5988 // remember the begin of the token
5989 m_start = m_cursor;
5990
5991
5992 {
5993 lexer_char_t yych;
5994 unsigned int yyaccept = 0;
5995 static const unsigned char yybm[] =
5996 {
5997 0, 0, 0, 0, 0, 0, 0, 0,
5998 0, 32, 32, 0, 0, 32, 0, 0,
5999 64, 64, 64, 64, 64, 64, 64, 64,
6000 64, 64, 64, 64, 64, 64, 64, 64,
6001 96, 64, 0, 64, 64, 64, 64, 64,
6002 64, 64, 64, 64, 64, 64, 64, 64,
6003 192, 192, 192, 192, 192, 192, 192, 192,
6004 192, 192, 64, 64, 64, 64, 64, 64,
6005 64, 64, 64, 64, 64, 64, 64, 64,
6006 64, 64, 64, 64, 64, 64, 64, 64,
6007 64, 64, 64, 64, 64, 64, 64, 64,
6008 64, 64, 64, 64, 0, 64, 64, 64,
6009 64, 64, 64, 64, 64, 64, 64, 64,
6010 64, 64, 64, 64, 64, 64, 64, 64,
6011 64, 64, 64, 64, 64, 64, 64, 64,
6012 64, 64, 64, 64, 64, 64, 64, 64,
6013 64, 64, 64, 64, 64, 64, 64, 64,
6014 64, 64, 64, 64, 64, 64, 64, 64,
6015 64, 64, 64, 64, 64, 64, 64, 64,
6016 64, 64, 64, 64, 64, 64, 64, 64,
6017 64, 64, 64, 64, 64, 64, 64, 64,
6018 64, 64, 64, 64, 64, 64, 64, 64,
6019 64, 64, 64, 64, 64, 64, 64, 64,
6020 64, 64, 64, 64, 64, 64, 64, 64,
6021 64, 64, 64, 64, 64, 64, 64, 64,
6022 64, 64, 64, 64, 64, 64, 64, 64,
6023 64, 64, 64, 64, 64, 64, 64, 64,
6024 64, 64, 64, 64, 64, 64, 64, 64,
6025 64, 64, 64, 64, 64, 64, 64, 64,
6026 64, 64, 64, 64, 64, 64, 64, 64,
6027 64, 64, 64, 64, 64, 64, 64, 64,
6028 64, 64, 64, 64, 64, 64, 64, 64,
6029 };
6030
6031 if ((m_limit - m_cursor) < 5)
6032 {
6033 yyfill(); // LCOV_EXCL_LINE;
6034 }
6035 yych = *m_cursor;
6036 if (yych <= '9')
6037 {
6038 if (yych <= ' ')
6039 {
6040 if (yych <= '\n')
6041 {
6042 if (yych <= 0x00)
6043 {
6044 goto basic_json_parser_27;
6045 }
6046 if (yych <= 0x08)
6047 {
6048 goto basic_json_parser_29;
6049 }
6050 if (yych >= '\n')
6051 {
6052 goto basic_json_parser_4;
6053 }
6054 }
6055 else
6056 {
6057 if (yych == '\r')
6058 {
6059 goto basic_json_parser_2;
6060 }
6061 if (yych <= 0x1F)
6062 {
6063 goto basic_json_parser_29;
6064 }
6065 }
6066 }
6067 else
6068 {
6069 if (yych <= ',')
6070 {
6071 if (yych == '"')
6072 {
6073 goto basic_json_parser_26;
6074 }
6075 if (yych <= '+')
6076 {
6077 goto basic_json_parser_29;
6078 }
6079 goto basic_json_parser_14;
6080 }
6081 else
6082 {
6083 if (yych <= '-')
6084 {
6085 goto basic_json_parser_22;
6086 }
6087 if (yych <= '/')
6088 {
6089 goto basic_json_parser_29;
6090 }
6091 if (yych <= '0')
6092 {
6093 goto basic_json_parser_23;
6094 }
6095 goto basic_json_parser_25;
6096 }
6097 }
6098 }
6099 else
6100 {
6101 if (yych <= 'm')
6102 {
6103 if (yych <= '\\')
6104 {
6105 if (yych <= ':')
6106 {
6107 goto basic_json_parser_16;
6108 }
6109 if (yych == '[')
6110 {
6111 goto basic_json_parser_6;
6112 }
6113 goto basic_json_parser_29;
6114 }
6115 else
6116 {
6117 if (yych <= ']')
6118 {
6119 goto basic_json_parser_8;
6120 }
6121 if (yych == 'f')
6122 {
6123 goto basic_json_parser_21;
6124 }
6125 goto basic_json_parser_29;
6126 }
6127 }
6128 else
6129 {
6130 if (yych <= 'z')
6131 {
6132 if (yych <= 'n')
6133 {
6134 goto basic_json_parser_18;
6135 }
6136 if (yych == 't')
6137 {
6138 goto basic_json_parser_20;
6139 }
6140 goto basic_json_parser_29;
6141 }
6142 else
6143 {
6144 if (yych <= '{')
6145 {
6146 goto basic_json_parser_10;
6147 }
6148 if (yych == '}')
6149 {
6150 goto basic_json_parser_12;
6151 }
6152 goto basic_json_parser_29;
6153 }
6154 }
6155 }
6156basic_json_parser_2:
6157 ++m_cursor;
6158 yych = *m_cursor;
6159 goto basic_json_parser_5;
6160basic_json_parser_3:
6161 {
6162 return scan();
6163 }
6164basic_json_parser_4:
6165 ++m_cursor;
6166 if (m_limit <= m_cursor)
6167 {
6168 yyfill(); // LCOV_EXCL_LINE;
6169 }
6170 yych = *m_cursor;
6171basic_json_parser_5:
6172 if (yybm[0 + yych] & 32)
6173 {
6174 goto basic_json_parser_4;
6175 }
6176 goto basic_json_parser_3;
6177basic_json_parser_6:
6178 ++m_cursor;
6179 {
6180 return token_type::begin_array;
6181 }
6182basic_json_parser_8:
6183 ++m_cursor;
6184 {
6185 return token_type::end_array;
6186 }
6187basic_json_parser_10:
6188 ++m_cursor;
6189 {
6190 return token_type::begin_object;
6191 }
6192basic_json_parser_12:
6193 ++m_cursor;
6194 {
6195 return token_type::end_object;
6196 }
6197basic_json_parser_14:
6198 ++m_cursor;
6199 {
6200 return token_type::value_separator;
6201 }
6202basic_json_parser_16:
6203 ++m_cursor;
6204 {
6205 return token_type::name_separator;
6206 }
6207basic_json_parser_18:
6208 yyaccept = 0;
6209 yych = *(m_marker = ++m_cursor);
6210 if (yych == 'u')
6211 {
6212 goto basic_json_parser_59;
6213 }
6214basic_json_parser_19:
6215 {
6216 return token_type::parse_error;
6217 }
6218basic_json_parser_20:
6219 yyaccept = 0;
6220 yych = *(m_marker = ++m_cursor);
6221 if (yych == 'r')
6222 {
6223 goto basic_json_parser_55;
6224 }
6225 goto basic_json_parser_19;
6226basic_json_parser_21:
6227 yyaccept = 0;
6228 yych = *(m_marker = ++m_cursor);
6229 if (yych == 'a')
6230 {
6231 goto basic_json_parser_50;
6232 }
6233 goto basic_json_parser_19;
6234basic_json_parser_22:
6235 yych = *++m_cursor;
6236 if (yych <= '/')
6237 {
6238 goto basic_json_parser_19;
6239 }
6240 if (yych <= '0')
6241 {
6242 goto basic_json_parser_49;
6243 }
6244 if (yych <= '9')
6245 {
6246 goto basic_json_parser_40;
6247 }
6248 goto basic_json_parser_19;
6249basic_json_parser_23:
6250 yyaccept = 1;
6251 yych = *(m_marker = ++m_cursor);
6252 if (yych <= 'D')
6253 {
6254 if (yych == '.')
6255 {
6256 goto basic_json_parser_42;
6257 }
6258 }
6259 else
6260 {
6261 if (yych <= 'E')
6262 {
6263 goto basic_json_parser_43;
6264 }
6265 if (yych == 'e')
6266 {
6267 goto basic_json_parser_43;
6268 }
6269 }
6270basic_json_parser_24:
6271 {
6272 return token_type::value_number;
6273 }
6274basic_json_parser_25:
6275 yyaccept = 1;
6276 yych = *(m_marker = ++m_cursor);
6277 goto basic_json_parser_41;
6278basic_json_parser_26:
6279 yyaccept = 0;
6280 yych = *(m_marker = ++m_cursor);
6281 if (yych <= 0x0F)
6282 {
6283 goto basic_json_parser_19;
6284 }
6285 goto basic_json_parser_31;
6286basic_json_parser_27:
6287 ++m_cursor;
6288 {
6289 return token_type::end_of_input;
6290 }
6291basic_json_parser_29:
6292 yych = *++m_cursor;
6293 goto basic_json_parser_19;
6294basic_json_parser_30:
6295 ++m_cursor;
6296 if (m_limit <= m_cursor)
6297 {
6298 yyfill(); // LCOV_EXCL_LINE;
6299 }
6300 yych = *m_cursor;
6301basic_json_parser_31:
6302 if (yybm[0 + yych] & 64)
6303 {
6304 goto basic_json_parser_30;
6305 }
6306 if (yych <= 0x0F)
6307 {
6308 goto basic_json_parser_32;
6309 }
6310 if (yych <= '"')
6311 {
6312 goto basic_json_parser_34;
6313 }
6314 goto basic_json_parser_33;
6315basic_json_parser_32:
6316 m_cursor = m_marker;
6317 if (yyaccept == 0)
6318 {
6319 goto basic_json_parser_19;
6320 }
6321 else
6322 {
6323 goto basic_json_parser_24;
6324 }
6325basic_json_parser_33:
6326 ++m_cursor;
6327 if (m_limit <= m_cursor)
6328 {
6329 yyfill(); // LCOV_EXCL_LINE;
6330 }
6331 yych = *m_cursor;
6332 if (yych <= 'e')
6333 {
6334 if (yych <= '/')
6335 {
6336 if (yych == '"')
6337 {
6338 goto basic_json_parser_30;
6339 }
6340 if (yych <= '.')
6341 {
6342 goto basic_json_parser_32;
6343 }
6344 goto basic_json_parser_30;
6345 }
6346 else
6347 {
6348 if (yych <= '\\')
6349 {
6350 if (yych <= '[')
6351 {
6352 goto basic_json_parser_32;
6353 }
6354 goto basic_json_parser_30;
6355 }
6356 else
6357 {
6358 if (yych == 'b')
6359 {
6360 goto basic_json_parser_30;
6361 }
6362 goto basic_json_parser_32;
6363 }
6364 }
6365 }
6366 else
6367 {
6368 if (yych <= 'q')
6369 {
6370 if (yych <= 'f')
6371 {
6372 goto basic_json_parser_30;
6373 }
6374 if (yych == 'n')
6375 {
6376 goto basic_json_parser_30;
6377 }
6378 goto basic_json_parser_32;
6379 }
6380 else
6381 {
6382 if (yych <= 's')
6383 {
6384 if (yych <= 'r')
6385 {
6386 goto basic_json_parser_30;
6387 }
6388 goto basic_json_parser_32;
6389 }
6390 else
6391 {
6392 if (yych <= 't')
6393 {
6394 goto basic_json_parser_30;
6395 }
6396 if (yych <= 'u')
6397 {
6398 goto basic_json_parser_36;
6399 }
6400 goto basic_json_parser_32;
6401 }
6402 }
6403 }
6404basic_json_parser_34:
6405 ++m_cursor;
6406 {
6407 return token_type::value_string;
6408 }
6409basic_json_parser_36:
6410 ++m_cursor;
6411 if (m_limit <= m_cursor)
6412 {
6413 yyfill(); // LCOV_EXCL_LINE;
6414 }
6415 yych = *m_cursor;
6416 if (yych <= '@')
6417 {
6418 if (yych <= '/')
6419 {
6420 goto basic_json_parser_32;
6421 }
6422 if (yych >= ':')
6423 {
6424 goto basic_json_parser_32;
6425 }
6426 }
6427 else
6428 {
6429 if (yych <= 'F')
6430 {
6431 goto basic_json_parser_37;
6432 }
6433 if (yych <= '`')
6434 {
6435 goto basic_json_parser_32;
6436 }
6437 if (yych >= 'g')
6438 {
6439 goto basic_json_parser_32;
6440 }
6441 }
6442basic_json_parser_37:
6443 ++m_cursor;
6444 if (m_limit <= m_cursor)
6445 {
6446 yyfill(); // LCOV_EXCL_LINE;
6447 }
6448 yych = *m_cursor;
6449 if (yych <= '@')
6450 {
6451 if (yych <= '/')
6452 {
6453 goto basic_json_parser_32;
6454 }
6455 if (yych >= ':')
6456 {
6457 goto basic_json_parser_32;
6458 }
6459 }
6460 else
6461 {
6462 if (yych <= 'F')
6463 {
6464 goto basic_json_parser_38;
6465 }
6466 if (yych <= '`')
6467 {
6468 goto basic_json_parser_32;
6469 }
6470 if (yych >= 'g')
6471 {
6472 goto basic_json_parser_32;
6473 }
6474 }
6475basic_json_parser_38:
6476 ++m_cursor;
6477 if (m_limit <= m_cursor)
6478 {
6479 yyfill(); // LCOV_EXCL_LINE;
6480 }
6481 yych = *m_cursor;
6482 if (yych <= '@')
6483 {
6484 if (yych <= '/')
6485 {
6486 goto basic_json_parser_32;
6487 }
6488 if (yych >= ':')
6489 {
6490 goto basic_json_parser_32;
6491 }
6492 }
6493 else
6494 {
6495 if (yych <= 'F')
6496 {
6497 goto basic_json_parser_39;
6498 }
6499 if (yych <= '`')
6500 {
6501 goto basic_json_parser_32;
6502 }
6503 if (yych >= 'g')
6504 {
6505 goto basic_json_parser_32;
6506 }
6507 }
6508basic_json_parser_39:
6509 ++m_cursor;
6510 if (m_limit <= m_cursor)
6511 {
6512 yyfill(); // LCOV_EXCL_LINE;
6513 }
6514 yych = *m_cursor;
6515 if (yych <= '@')
6516 {
6517 if (yych <= '/')
6518 {
6519 goto basic_json_parser_32;
6520 }
6521 if (yych <= '9')
6522 {
6523 goto basic_json_parser_30;
6524 }
6525 goto basic_json_parser_32;
6526 }
6527 else
6528 {
6529 if (yych <= 'F')
6530 {
6531 goto basic_json_parser_30;
6532 }
6533 if (yych <= '`')
6534 {
6535 goto basic_json_parser_32;
6536 }
6537 if (yych <= 'f')
6538 {
6539 goto basic_json_parser_30;
6540 }
6541 goto basic_json_parser_32;
6542 }
6543basic_json_parser_40:
6544 yyaccept = 1;
6545 m_marker = ++m_cursor;
6546 if ((m_limit - m_cursor) < 3)
6547 {
6548 yyfill(); // LCOV_EXCL_LINE;
6549 }
6550 yych = *m_cursor;
6551basic_json_parser_41:
6552 if (yybm[0 + yych] & 128)
6553 {
6554 goto basic_json_parser_40;
6555 }
6556 if (yych <= 'D')
6557 {
6558 if (yych != '.')
6559 {
6560 goto basic_json_parser_24;
6561 }
6562 }
6563 else
6564 {
6565 if (yych <= 'E')
6566 {
6567 goto basic_json_parser_43;
6568 }
6569 if (yych == 'e')
6570 {
6571 goto basic_json_parser_43;
6572 }
6573 goto basic_json_parser_24;
6574 }
6575basic_json_parser_42:
6576 yych = *++m_cursor;
6577 if (yych <= '/')
6578 {
6579 goto basic_json_parser_32;
6580 }
6581 if (yych <= '9')
6582 {
6583 goto basic_json_parser_47;
6584 }
6585 goto basic_json_parser_32;
6586basic_json_parser_43:
6587 yych = *++m_cursor;
6588 if (yych <= ',')
6589 {
6590 if (yych != '+')
6591 {
6592 goto basic_json_parser_32;
6593 }
6594 }
6595 else
6596 {
6597 if (yych <= '-')
6598 {
6599 goto basic_json_parser_44;
6600 }
6601 if (yych <= '/')
6602 {
6603 goto basic_json_parser_32;
6604 }
6605 if (yych <= '9')
6606 {
6607 goto basic_json_parser_45;
6608 }
6609 goto basic_json_parser_32;
6610 }
6611basic_json_parser_44:
6612 yych = *++m_cursor;
6613 if (yych <= '/')
6614 {
6615 goto basic_json_parser_32;
6616 }
6617 if (yych >= ':')
6618 {
6619 goto basic_json_parser_32;
6620 }
6621basic_json_parser_45:
6622 ++m_cursor;
6623 if (m_limit <= m_cursor)
6624 {
6625 yyfill(); // LCOV_EXCL_LINE;
6626 }
6627 yych = *m_cursor;
6628 if (yych <= '/')
6629 {
6630 goto basic_json_parser_24;
6631 }
6632 if (yych <= '9')
6633 {
6634 goto basic_json_parser_45;
6635 }
6636 goto basic_json_parser_24;
6637basic_json_parser_47:
6638 yyaccept = 1;
6639 m_marker = ++m_cursor;
6640 if ((m_limit - m_cursor) < 3)
6641 {
6642 yyfill(); // LCOV_EXCL_LINE;
6643 }
6644 yych = *m_cursor;
6645 if (yych <= 'D')
6646 {
6647 if (yych <= '/')
6648 {
6649 goto basic_json_parser_24;
6650 }
6651 if (yych <= '9')
6652 {
6653 goto basic_json_parser_47;
6654 }
6655 goto basic_json_parser_24;
6656 }
6657 else
6658 {
6659 if (yych <= 'E')
6660 {
6661 goto basic_json_parser_43;
6662 }
6663 if (yych == 'e')
6664 {
6665 goto basic_json_parser_43;
6666 }
6667 goto basic_json_parser_24;
6668 }
6669basic_json_parser_49:
6670 yyaccept = 1;
6671 yych = *(m_marker = ++m_cursor);
6672 if (yych <= 'D')
6673 {
6674 if (yych == '.')
6675 {
6676 goto basic_json_parser_42;
6677 }
6678 goto basic_json_parser_24;
6679 }
6680 else
6681 {
6682 if (yych <= 'E')
6683 {
6684 goto basic_json_parser_43;
6685 }
6686 if (yych == 'e')
6687 {
6688 goto basic_json_parser_43;
6689 }
6690 goto basic_json_parser_24;
6691 }
6692basic_json_parser_50:
6693 yych = *++m_cursor;
6694 if (yych != 'l')
6695 {
6696 goto basic_json_parser_32;
6697 }
6698 yych = *++m_cursor;
6699 if (yych != 's')
6700 {
6701 goto basic_json_parser_32;
6702 }
6703 yych = *++m_cursor;
6704 if (yych != 'e')
6705 {
6706 goto basic_json_parser_32;
6707 }
6708 ++m_cursor;
6709 {
6710 return token_type::literal_false;
6711 }
6712basic_json_parser_55:
6713 yych = *++m_cursor;
6714 if (yych != 'u')
6715 {
6716 goto basic_json_parser_32;
6717 }
6718 yych = *++m_cursor;
6719 if (yych != 'e')
6720 {
6721 goto basic_json_parser_32;
6722 }
6723 ++m_cursor;
6724 {
6725 return token_type::literal_true;
6726 }
6727basic_json_parser_59:
6728 yych = *++m_cursor;
6729 if (yych != 'l')
6730 {
6731 goto basic_json_parser_32;
6732 }
6733 yych = *++m_cursor;
6734 if (yych != 'l')
6735 {
6736 goto basic_json_parser_32;
6737 }
6738 ++m_cursor;
6739 {
6740 return token_type::literal_null;
6741 }
6742 }
6743
6744
6745 }
6746
6747 /// append data from the stream to the internal buffer
6748 void yyfill() noexcept
6749 {
6750 if (not m_stream or not * m_stream)
6751 {
6752 return;
6753 }
6754
6755 const ssize_t offset_start = m_start - m_content;
6756 const ssize_t offset_marker = m_marker - m_start;
6757 const ssize_t offset_cursor = m_cursor - m_start;
6758
6759 m_buffer.erase(0, static_cast<size_t>(offset_start));
6760 std::string line;
6761 std::getline(*m_stream, line);
6762 m_buffer += "\n" + line; // add line with newline symbol
6763
6764 m_content = reinterpret_cast<const lexer_char_t*>(m_buffer.c_str());
6765 m_start = m_content;
6766 m_marker = m_start + offset_marker;
6767 m_cursor = m_start + offset_cursor;
6768 m_limit = m_start + m_buffer.size() - 1;
6769 }
6770
6771 /// return string representation of last read token
6772 string_t get_token() const noexcept
6773 {
6774 return string_t(reinterpret_cast<typename string_t::const_pointer>(m_start),
6775 static_cast<size_t>(m_cursor - m_start));
6776 }
6777
6778 /*!
6779 @brief return string value for string tokens
6780
6781 The function iterates the characters between the opening and closing
6782 quotes of the string value. The complete string is the range
6783 [m_start,m_cursor). Consequently, we iterate from m_start+1 to
6784 m_cursor-1.
6785
6786 We differentiate two cases:
6787
6788 1. Escaped characters. In this case, a new character is constructed
6789 according to the nature of the escape. Some escapes create new
6790 characters (e.g., @c "\\n" is replaced by @c "\n"), some are copied
6791 as is (e.g., @c "\\\\"). Furthermore, Unicode escapes of the shape
6792 @c "\\uxxxx" need special care. In this case, to_unicode takes care
6793 of the construction of the values.
6794 2. Unescaped characters are copied as is.
6795
6796 @return string value of current token without opening and closing quotes
6797 @throw std::out_of_range if to_unicode fails
6798 */
6799 string_t get_string() const
6800 {
6801 string_t result;
6802 result.reserve(static_cast<size_t>(m_cursor - m_start - 2));
6803
6804 // iterate the result between the quotes
6805 for (const lexer_char_t* i = m_start + 1; i < m_cursor - 1; ++i)
6806 {
6807 // process escaped characters
6808 if (*i == '\\')
6809 {
6810 // read next character
6811 ++i;
6812
6813 switch (*i)
6814 {
6815 // the default escapes
6816 case 't':
6817 {
6818 result += "\t";
6819 break;
6820 }
6821 case 'b':
6822 {
6823 result += "\b";
6824 break;
6825 }
6826 case 'f':
6827 {
6828 result += "\f";
6829 break;
6830 }
6831 case 'n':
6832 {
6833 result += "\n";
6834 break;
6835 }
6836 case 'r':
6837 {
6838 result += "\r";
6839 break;
6840 }
6841 case '\\':
6842 {
6843 result += "\\";
6844 break;
6845 }
6846 case '/':
6847 {
6848 result += "/";
6849 break;
6850 }
6851 case '"':
6852 {
6853 result += "\"";
6854 break;
6855 }
6856
6857 // unicode
6858 case 'u':
6859 {
6860 // get code xxxx from uxxxx
6861 auto codepoint = std::strtoul(std::string(reinterpret_cast<typename string_t::const_pointer>(i + 1),
6862 4).c_str(), nullptr, 16);
6863
6864 // check if codepoint is a high surrogate
6865 if (codepoint >= 0xD800 and codepoint <= 0xDBFF)
6866 {
6867 // make sure there is a subsequent unicode
6868 if ((i + 6 >= m_limit) or * (i + 5) != '\\' or * (i + 6) != 'u')
6869 {
6870 throw std::invalid_argument("missing low surrogate");
6871 }
6872
6873 // get code yyyy from uxxxx\uyyyy
6874 auto codepoint2 = std::strtoul(std::string(reinterpret_cast<typename string_t::const_pointer>
6875 (i + 7), 4).c_str(), nullptr, 16);
6876 result += to_unicode(codepoint, codepoint2);
6877 // skip the next 11 characters (xxxx\uyyyy)
6878 i += 11;
6879 }
6880 else
6881 {
6882 // add unicode character(s)
6883 result += to_unicode(codepoint);
6884 // skip the next four characters (xxxx)
6885 i += 4;
6886 }
6887 break;
6888 }
6889 }
6890 }
6891 else
6892 {
6893 // all other characters are just copied to the end of the
6894 // string
6895 result.append(1, static_cast<typename string_t::value_type>(*i));
6896 }
6897 }
6898
6899 return result;
6900 }
6901
6902 /*!
6903 @brief return number value for number tokens
6904
6905 This function translates the last token into a floating point number.
6906 The pointer m_begin points to the beginning of the parsed number. We
6907 pass this pointer to std::strtod which sets endptr to the first
6908 character past the converted number. If this pointer is not the same as
6909 m_cursor, then either more or less characters have been used during the
6910 comparison. This can happen for inputs like "01" which will be treated
6911 like number 0 followed by number 1.
6912
6913 @return the result of the number conversion or NAN if the conversion
6914 read past the current token. The latter case needs to be treated by the
6915 caller function.
6916
6917 @throw std::range_error if passed value is out of range
6918 */
6919 long double get_number() const
6920 {
6921 // conversion
6922 typename string_t::value_type* endptr;
6923 const auto float_val = std::strtold(reinterpret_cast<typename string_t::const_pointer>(m_start),
6924 &endptr);
6925
6926 // return float_val if the whole number was translated and NAN
6927 // otherwise
6928 return (reinterpret_cast<lexer_char_t*>(endptr) == m_cursor) ? float_val : NAN;
6929 }
6930
6931 private:
6932 /// optional input stream
6933 std::istream* m_stream;
6934 /// the buffer
6935 string_t m_buffer;
6936 /// the buffer pointer
6937 const lexer_char_t* m_content = nullptr;
6938 /// pointer to the beginning of the current symbol
6939 const lexer_char_t* m_start = nullptr;
6940 /// pointer for backtracking information
6941 const lexer_char_t* m_marker = nullptr;
6942 /// pointer to the current symbol
6943 const lexer_char_t* m_cursor = nullptr;
6944 /// pointer to the end of the buffer
6945 const lexer_char_t* m_limit = nullptr;
6946 };
6947
6948 /*!
6949 @brief syntax analysis
6950 */
6951 class parser
6952 {
6953 public:
6954 /// constructor for strings
6955 parser(const string_t& s, parser_callback_t cb = nullptr)
6956 : callback(cb), m_lexer(s)
6957 {
6958 // read first token
6959 get_token();
6960 }
6961
6962 /// a parser reading from an input stream
6963 parser(std::istream& _is, parser_callback_t cb = nullptr)
6964 : callback(cb), m_lexer(&_is)
6965 {
6966 // read first token
6967 get_token();
6968 }
6969
6970 /// public parser interface
6971 basic_json parse()
6972 {
6973 basic_json result = parse_internal(true);
6974
6975 expect(lexer::token_type::end_of_input);
6976
6977 // return parser result and replace it with null in case the
6978 // top-level value was discarded by the callback function
6979 return result.is_discarded() ? basic_json() : result;
6980 }
6981
6982 private:
6983 /// the actual parser
6984 basic_json parse_internal(bool keep)
6985 {
6986 auto result = basic_json(value_t::discarded);
6987
6988 switch (last_token)
6989 {
6990 case (lexer::token_type::begin_object):
6991 {
6992 if (keep and (not callback or (keep = callback(depth++, parse_event_t::object_start, result))))
6993 {
6994 // explicitly set result to object to cope with {}
6995 result.m_type = value_t::object;
6996 result.m_value = json_value(value_t::object);
6997 }
6998
6999 // read next token
7000 get_token();
7001
7002 // closing } -> we are done
7003 if (last_token == lexer::token_type::end_object)
7004 {
7005 get_token();
7006 if (keep and callback and not callback(--depth, parse_event_t::object_end, result))
7007 {
7008 result = basic_json(value_t::discarded);
7009 }
7010 return result;
7011 }
7012
7013 // no comma is expected here
7014 unexpect(lexer::token_type::value_separator);
7015
7016 // otherwise: parse key-value pairs
7017 do
7018 {
7019 // ugly, but could be fixed with loop reorganization
7020 if (last_token == lexer::token_type::value_separator)
7021 {
7022 get_token();
7023 }
7024
7025 // store key
7026 expect(lexer::token_type::value_string);
7027 const auto key = m_lexer.get_string();
7028
7029 bool keep_tag = false;
7030 if (keep)
7031 {
7032 if (callback)
7033 {
7034 basic_json k(key);
7035 keep_tag = callback(depth, parse_event_t::key, k);
7036 }
7037 else
7038 {
7039 keep_tag = true;
7040 }
7041 }
7042
7043 // parse separator (:)
7044 get_token();
7045 expect(lexer::token_type::name_separator);
7046
7047 // parse and add value
7048 get_token();
7049 auto value = parse_internal(keep);
7050 if (keep and keep_tag and not value.is_discarded())
7051 {
7052 result[key] = std::move(value);
7053 }
7054 }
7055 while (last_token == lexer::token_type::value_separator);
7056
7057 // closing }
7058 expect(lexer::token_type::end_object);
7059 get_token();
7060 if (keep and callback and not callback(--depth, parse_event_t::object_end, result))
7061 {
7062 result = basic_json(value_t::discarded);
7063 }
7064
7065 return result;
7066 }
7067
7068 case (lexer::token_type::begin_array):
7069 {
7070 if (keep and (not callback or (keep = callback(depth++, parse_event_t::array_start, result))))
7071 {
7072 // explicitly set result to object to cope with []
7073 result.m_type = value_t::array;
7074 result.m_value = json_value(value_t::array);
7075 }
7076
7077 // read next token
7078 get_token();
7079
7080 // closing ] -> we are done
7081 if (last_token == lexer::token_type::end_array)
7082 {
7083 get_token();
7084 if (callback and not callback(--depth, parse_event_t::array_end, result))
7085 {
7086 result = basic_json(value_t::discarded);
7087 }
7088 return result;
7089 }
7090
7091 // no comma is expected here
7092 unexpect(lexer::token_type::value_separator);
7093
7094 // otherwise: parse values
7095 do
7096 {
7097 // ugly, but could be fixed with loop reorganization
7098 if (last_token == lexer::token_type::value_separator)
7099 {
7100 get_token();
7101 }
7102
7103 // parse value
7104 auto value = parse_internal(keep);
7105 if (keep and not value.is_discarded())
7106 {
7107 result.push_back(std::move(value));
7108 }
7109 }
7110 while (last_token == lexer::token_type::value_separator);
7111
7112 // closing ]
7113 expect(lexer::token_type::end_array);
7114 get_token();
7115 if (keep and callback and not callback(--depth, parse_event_t::array_end, result))
7116 {
7117 result = basic_json(value_t::discarded);
7118 }
7119
7120 return result;
7121 }
7122
7123 case (lexer::token_type::literal_null):
7124 {
7125 get_token();
7126 result.m_type = value_t::null;
7127 break;
7128 }
7129
7130 case (lexer::token_type::value_string):
7131 {
7132 const auto s = m_lexer.get_string();
7133 get_token();
7134 result = basic_json(s);
7135 break;
7136 }
7137
7138 case (lexer::token_type::literal_true):
7139 {
7140 get_token();
7141 result.m_type = value_t::boolean;
7142 result.m_value = true;
7143 break;
7144 }
7145
7146 case (lexer::token_type::literal_false):
7147 {
7148 get_token();
7149 result.m_type = value_t::boolean;
7150 result.m_value = false;
7151 break;
7152 }
7153
7154 case (lexer::token_type::value_number):
7155 {
7156 auto float_val = m_lexer.get_number();
7157
7158 // NAN is returned if token could not be translated
7159 // completely
7160 if (std::isnan(float_val))
7161 {
7162 throw std::invalid_argument(std::string("parse error - ") +
7163 m_lexer.get_token() + " is not a number");
7164 }
7165
7166 get_token();
7167
7168 // check if conversion loses precision
7169 const auto int_val = static_cast<number_integer_t>(float_val);
7170 if (approx(float_val, static_cast<long double>(int_val)))
7171 {
7172 // we basic_json not lose precision -> return int
7173 result.m_type = value_t::number_integer;
7174 result.m_value = int_val;
7175 }
7176 else
7177 {
7178 // we would lose precision -> returnfloat
7179 result.m_type = value_t::number_float;
7180 result.m_value = static_cast<number_float_t>(float_val);
7181 }
7182 break;
7183 }
7184
7185 default:
7186 {
7187 // the last token was unexpected
7188 unexpect(last_token);
7189 }
7190 }
7191
7192 if (keep and callback and not callback(depth, parse_event_t::value, result))
7193 {
7194 result = basic_json(value_t::discarded);
7195 }
7196 return result;
7197 }
7198
7199 /// get next token from lexer
7200 typename lexer::token_type get_token()
7201 {
7202 last_token = m_lexer.scan();
7203 return last_token;
7204 }
7205
7206 void expect(typename lexer::token_type t) const
7207 {
7208 if (t != last_token)
7209 {
7210 std::string error_msg = "parse error - unexpected \'";
7211 error_msg += m_lexer.get_token();
7212 error_msg += "\' (" + lexer::token_type_name(last_token);
7213 error_msg += "); expected " + lexer::token_type_name(t);
7214 throw std::invalid_argument(error_msg);
7215 }
7216 }
7217
7218 void unexpect(typename lexer::token_type t) const
7219 {
7220 if (t == last_token)
7221 {
7222 std::string error_msg = "parse error - unexpected \'";
7223 error_msg += m_lexer.get_token();
7224 error_msg += "\' (";
7225 error_msg += lexer::token_type_name(last_token) + ")";
7226 throw std::invalid_argument(error_msg);
7227 }
7228 }
7229
7230 private:
7231 /// current level of recursion
7232 int depth = 0;
7233 /// callback function
7234 parser_callback_t callback;
7235 /// the type of the last read token
7236 typename lexer::token_type last_token = lexer::token_type::uninitialized;
7237 /// the lexer
7238 lexer m_lexer;
7239 };
7240};
7241
7242
7243/////////////
7244// presets //
7245/////////////
7246
7247/*!
7248@brief default JSON class
7249
7250This type is the default specialization of the @ref basic_json class which uses
7251the standard template types.
7252*/
7253using json = basic_json<>;
7254}
7255
7256
7257/////////////////////////
7258// nonmember functions //
7259/////////////////////////
7260
7261// specialization of std::swap, and std::hash
7262namespace std
7263{
7264/*!
7265@brief exchanges the values of two JSON objects
7266*/
7267template <>
7268inline void swap(nlohmann::json& j1,
7269 nlohmann::json& j2) noexcept(
7270 is_nothrow_move_constructible<nlohmann::json>::value and
7271 is_nothrow_move_assignable<nlohmann::json>::value
7272 )
7273{
7274 j1.swap(j2);
7275}
7276
7277/// hash value for JSON objects
7278template <>
7279struct hash<nlohmann::json>
7280{
7281 /// return a hash value for a JSON object
7282 std::size_t operator()(const nlohmann::json& j) const
7283 {
7284 // a naive hashing via the string representation
7285 const auto& h = hash<nlohmann::json::string_t>();
7286 return h(j.dump());
7287 }
7288};
7289}
7290
7291/*!
7292@brief user-defined string literal for JSON values
7293
7294This operator implements a user-defined string literal for JSON objects. It can
7295be used by adding \p "_json" to a string literal and returns a JSON object if
7296no parse error occurred.
7297
7298@param[in] s a string representation of a JSON object
7299@return a JSON object
7300*/
7301inline nlohmann::json operator "" _json(const char* s, std::size_t)
7302{
7303 return nlohmann::json::parse(reinterpret_cast<nlohmann::json::string_t::value_type*>
7304 (const_cast<char*>(s)));
7305}
7306
7307#endif
diff --git a/ddl/out/IR.cpp b/ddl/out/IR.cpp
new file mode 100644
index 0000000..729bdd9
--- /dev/null
+++ b/ddl/out/IR.cpp
@@ -0,0 +1,2864 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.420877000000Z
3
4#include "IR.hpp"
5template<> json toJSON<std::shared_ptr<ArrayValue>>(std::shared_ptr<ArrayValue> &v) {
6 json obj({});
7 switch (v->tag) {
8 case ::ArrayValue::tag::VBoolArray:
9 obj["tag"] = "VBoolArray";
10 {
11 std::shared_ptr<data::VBoolArray> tv = std::static_pointer_cast<data::VBoolArray>(v);
12 obj["arg0"] = toJSON(tv->_0);
13 }
14 break;
15 case ::ArrayValue::tag::VIntArray:
16 obj["tag"] = "VIntArray";
17 {
18 std::shared_ptr<data::VIntArray> tv = std::static_pointer_cast<data::VIntArray>(v);
19 obj["arg0"] = toJSON(tv->_0);
20 }
21 break;
22 case ::ArrayValue::tag::VWordArray:
23 obj["tag"] = "VWordArray";
24 {
25 std::shared_ptr<data::VWordArray> tv = std::static_pointer_cast<data::VWordArray>(v);
26 obj["arg0"] = toJSON(tv->_0);
27 }
28 break;
29 case ::ArrayValue::tag::VFloatArray:
30 obj["tag"] = "VFloatArray";
31 {
32 std::shared_ptr<data::VFloatArray> tv = std::static_pointer_cast<data::VFloatArray>(v);
33 obj["arg0"] = toJSON(tv->_0);
34 }
35 break;
36 }
37 return obj;
38}
39
40template<> std::shared_ptr<ArrayValue> fromJSON<std::shared_ptr<ArrayValue>>(W<std::shared_ptr<ArrayValue>> v, json &obj) {
41 enum ::ArrayValue::tag tagType;
42 std::string tag = obj["tag"];
43 if (tag == "VBoolArray") {
44 tagType = ::ArrayValue::tag::VBoolArray;
45 std::shared_ptr<data::VBoolArray> tv(new data::VBoolArray());
46 tv->_0 = fromJSON(W<std::vector<Bool>>(), obj["arg0"]);
47 return tv;
48 }
49 else if (tag == "VIntArray") {
50 tagType = ::ArrayValue::tag::VIntArray;
51 std::shared_ptr<data::VIntArray> tv(new data::VIntArray());
52 tv->_0 = fromJSON(W<std::vector<Int32>>(), obj["arg0"]);
53 return tv;
54 }
55 else if (tag == "VWordArray") {
56 tagType = ::ArrayValue::tag::VWordArray;
57 std::shared_ptr<data::VWordArray> tv(new data::VWordArray());
58 tv->_0 = fromJSON(W<std::vector<Word32>>(), obj["arg0"]);
59 return tv;
60 }
61 else if (tag == "VFloatArray") {
62 tagType = ::ArrayValue::tag::VFloatArray;
63 std::shared_ptr<data::VFloatArray> tv(new data::VFloatArray());
64 tv->_0 = fromJSON(W<std::vector<Float>>(), obj["arg0"]);
65 return tv;
66 }
67 else throw "unknown constructor: " + tag;
68 std::shared_ptr<::ArrayValue> o(new ::ArrayValue());
69 o->tag = tagType;
70 return o;
71}
72
73template<> json toJSON<std::shared_ptr<Value>>(std::shared_ptr<Value> &v) {
74 json obj({});
75 switch (v->tag) {
76 case ::Value::tag::VBool:
77 obj["tag"] = "VBool";
78 {
79 std::shared_ptr<data::VBool> tv = std::static_pointer_cast<data::VBool>(v);
80 obj["arg0"] = toJSON(tv->_0);
81 }
82 break;
83 case ::Value::tag::VV2B:
84 obj["tag"] = "VV2B";
85 {
86 std::shared_ptr<data::VV2B> tv = std::static_pointer_cast<data::VV2B>(v);
87 obj["arg0"] = toJSON(tv->_0);
88 }
89 break;
90 case ::Value::tag::VV3B:
91 obj["tag"] = "VV3B";
92 {
93 std::shared_ptr<data::VV3B> tv = std::static_pointer_cast<data::VV3B>(v);
94 obj["arg0"] = toJSON(tv->_0);
95 }
96 break;
97 case ::Value::tag::VV4B:
98 obj["tag"] = "VV4B";
99 {
100 std::shared_ptr<data::VV4B> tv = std::static_pointer_cast<data::VV4B>(v);
101 obj["arg0"] = toJSON(tv->_0);
102 }
103 break;
104 case ::Value::tag::VWord:
105 obj["tag"] = "VWord";
106 {
107 std::shared_ptr<data::VWord> tv = std::static_pointer_cast<data::VWord>(v);
108 obj["arg0"] = toJSON(tv->_0);
109 }
110 break;
111 case ::Value::tag::VV2U:
112 obj["tag"] = "VV2U";
113 {
114 std::shared_ptr<data::VV2U> tv = std::static_pointer_cast<data::VV2U>(v);
115 obj["arg0"] = toJSON(tv->_0);
116 }
117 break;
118 case ::Value::tag::VV3U:
119 obj["tag"] = "VV3U";
120 {
121 std::shared_ptr<data::VV3U> tv = std::static_pointer_cast<data::VV3U>(v);
122 obj["arg0"] = toJSON(tv->_0);
123 }
124 break;
125 case ::Value::tag::VV4U:
126 obj["tag"] = "VV4U";
127 {
128 std::shared_ptr<data::VV4U> tv = std::static_pointer_cast<data::VV4U>(v);
129 obj["arg0"] = toJSON(tv->_0);
130 }
131 break;
132 case ::Value::tag::VInt:
133 obj["tag"] = "VInt";
134 {
135 std::shared_ptr<data::VInt> tv = std::static_pointer_cast<data::VInt>(v);
136 obj["arg0"] = toJSON(tv->_0);
137 }
138 break;
139 case ::Value::tag::VV2I:
140 obj["tag"] = "VV2I";
141 {
142 std::shared_ptr<data::VV2I> tv = std::static_pointer_cast<data::VV2I>(v);
143 obj["arg0"] = toJSON(tv->_0);
144 }
145 break;
146 case ::Value::tag::VV3I:
147 obj["tag"] = "VV3I";
148 {
149 std::shared_ptr<data::VV3I> tv = std::static_pointer_cast<data::VV3I>(v);
150 obj["arg0"] = toJSON(tv->_0);
151 }
152 break;
153 case ::Value::tag::VV4I:
154 obj["tag"] = "VV4I";
155 {
156 std::shared_ptr<data::VV4I> tv = std::static_pointer_cast<data::VV4I>(v);
157 obj["arg0"] = toJSON(tv->_0);
158 }
159 break;
160 case ::Value::tag::VFloat:
161 obj["tag"] = "VFloat";
162 {
163 std::shared_ptr<data::VFloat> tv = std::static_pointer_cast<data::VFloat>(v);
164 obj["arg0"] = toJSON(tv->_0);
165 }
166 break;
167 case ::Value::tag::VV2F:
168 obj["tag"] = "VV2F";
169 {
170 std::shared_ptr<data::VV2F> tv = std::static_pointer_cast<data::VV2F>(v);
171 obj["arg0"] = toJSON(tv->_0);
172 }
173 break;
174 case ::Value::tag::VV3F:
175 obj["tag"] = "VV3F";
176 {
177 std::shared_ptr<data::VV3F> tv = std::static_pointer_cast<data::VV3F>(v);
178 obj["arg0"] = toJSON(tv->_0);
179 }
180 break;
181 case ::Value::tag::VV4F:
182 obj["tag"] = "VV4F";
183 {
184 std::shared_ptr<data::VV4F> tv = std::static_pointer_cast<data::VV4F>(v);
185 obj["arg0"] = toJSON(tv->_0);
186 }
187 break;
188 case ::Value::tag::VM22F:
189 obj["tag"] = "VM22F";
190 {
191 std::shared_ptr<data::VM22F> tv = std::static_pointer_cast<data::VM22F>(v);
192 obj["arg0"] = toJSON(tv->_0);
193 }
194 break;
195 case ::Value::tag::VM23F:
196 obj["tag"] = "VM23F";
197 {
198 std::shared_ptr<data::VM23F> tv = std::static_pointer_cast<data::VM23F>(v);
199 obj["arg0"] = toJSON(tv->_0);
200 }
201 break;
202 case ::Value::tag::VM24F:
203 obj["tag"] = "VM24F";
204 {
205 std::shared_ptr<data::VM24F> tv = std::static_pointer_cast<data::VM24F>(v);
206 obj["arg0"] = toJSON(tv->_0);
207 }
208 break;
209 case ::Value::tag::VM32F:
210 obj["tag"] = "VM32F";
211 {
212 std::shared_ptr<data::VM32F> tv = std::static_pointer_cast<data::VM32F>(v);
213 obj["arg0"] = toJSON(tv->_0);
214 }
215 break;
216 case ::Value::tag::VM33F:
217 obj["tag"] = "VM33F";
218 {
219 std::shared_ptr<data::VM33F> tv = std::static_pointer_cast<data::VM33F>(v);
220 obj["arg0"] = toJSON(tv->_0);
221 }
222 break;
223 case ::Value::tag::VM34F:
224 obj["tag"] = "VM34F";
225 {
226 std::shared_ptr<data::VM34F> tv = std::static_pointer_cast<data::VM34F>(v);
227 obj["arg0"] = toJSON(tv->_0);
228 }
229 break;
230 case ::Value::tag::VM42F:
231 obj["tag"] = "VM42F";
232 {
233 std::shared_ptr<data::VM42F> tv = std::static_pointer_cast<data::VM42F>(v);
234 obj["arg0"] = toJSON(tv->_0);
235 }
236 break;
237 case ::Value::tag::VM43F:
238 obj["tag"] = "VM43F";
239 {
240 std::shared_ptr<data::VM43F> tv = std::static_pointer_cast<data::VM43F>(v);
241 obj["arg0"] = toJSON(tv->_0);
242 }
243 break;
244 case ::Value::tag::VM44F:
245 obj["tag"] = "VM44F";
246 {
247 std::shared_ptr<data::VM44F> tv = std::static_pointer_cast<data::VM44F>(v);
248 obj["arg0"] = toJSON(tv->_0);
249 }
250 break;
251 }
252 return obj;
253}
254
255template<> std::shared_ptr<Value> fromJSON<std::shared_ptr<Value>>(W<std::shared_ptr<Value>> v, json &obj) {
256 enum ::Value::tag tagType;
257 std::string tag = obj["tag"];
258 if (tag == "VBool") {
259 tagType = ::Value::tag::VBool;
260 std::shared_ptr<data::VBool> tv(new data::VBool());
261 tv->_0 = fromJSON(W<Bool>(), obj["arg0"]);
262 return tv;
263 }
264 else if (tag == "VV2B") {
265 tagType = ::Value::tag::VV2B;
266 std::shared_ptr<data::VV2B> tv(new data::VV2B());
267 tv->_0 = fromJSON(W<V2B>(), obj["arg0"]);
268 return tv;
269 }
270 else if (tag == "VV3B") {
271 tagType = ::Value::tag::VV3B;
272 std::shared_ptr<data::VV3B> tv(new data::VV3B());
273 tv->_0 = fromJSON(W<V3B>(), obj["arg0"]);
274 return tv;
275 }
276 else if (tag == "VV4B") {
277 tagType = ::Value::tag::VV4B;
278 std::shared_ptr<data::VV4B> tv(new data::VV4B());
279 tv->_0 = fromJSON(W<V4B>(), obj["arg0"]);
280 return tv;
281 }
282 else if (tag == "VWord") {
283 tagType = ::Value::tag::VWord;
284 std::shared_ptr<data::VWord> tv(new data::VWord());
285 tv->_0 = fromJSON(W<Word32>(), obj["arg0"]);
286 return tv;
287 }
288 else if (tag == "VV2U") {
289 tagType = ::Value::tag::VV2U;
290 std::shared_ptr<data::VV2U> tv(new data::VV2U());
291 tv->_0 = fromJSON(W<V2U>(), obj["arg0"]);
292 return tv;
293 }
294 else if (tag == "VV3U") {
295 tagType = ::Value::tag::VV3U;
296 std::shared_ptr<data::VV3U> tv(new data::VV3U());
297 tv->_0 = fromJSON(W<V3U>(), obj["arg0"]);
298 return tv;
299 }
300 else if (tag == "VV4U") {
301 tagType = ::Value::tag::VV4U;
302 std::shared_ptr<data::VV4U> tv(new data::VV4U());
303 tv->_0 = fromJSON(W<V4U>(), obj["arg0"]);
304 return tv;
305 }
306 else if (tag == "VInt") {
307 tagType = ::Value::tag::VInt;
308 std::shared_ptr<data::VInt> tv(new data::VInt());
309 tv->_0 = fromJSON(W<Int32>(), obj["arg0"]);
310 return tv;
311 }
312 else if (tag == "VV2I") {
313 tagType = ::Value::tag::VV2I;
314 std::shared_ptr<data::VV2I> tv(new data::VV2I());
315 tv->_0 = fromJSON(W<V2I>(), obj["arg0"]);
316 return tv;
317 }
318 else if (tag == "VV3I") {
319 tagType = ::Value::tag::VV3I;
320 std::shared_ptr<data::VV3I> tv(new data::VV3I());
321 tv->_0 = fromJSON(W<V3I>(), obj["arg0"]);
322 return tv;
323 }
324 else if (tag == "VV4I") {
325 tagType = ::Value::tag::VV4I;
326 std::shared_ptr<data::VV4I> tv(new data::VV4I());
327 tv->_0 = fromJSON(W<V4I>(), obj["arg0"]);
328 return tv;
329 }
330 else if (tag == "VFloat") {
331 tagType = ::Value::tag::VFloat;
332 std::shared_ptr<data::VFloat> tv(new data::VFloat());
333 tv->_0 = fromJSON(W<Float>(), obj["arg0"]);
334 return tv;
335 }
336 else if (tag == "VV2F") {
337 tagType = ::Value::tag::VV2F;
338 std::shared_ptr<data::VV2F> tv(new data::VV2F());
339 tv->_0 = fromJSON(W<V2F>(), obj["arg0"]);
340 return tv;
341 }
342 else if (tag == "VV3F") {
343 tagType = ::Value::tag::VV3F;
344 std::shared_ptr<data::VV3F> tv(new data::VV3F());
345 tv->_0 = fromJSON(W<V3F>(), obj["arg0"]);
346 return tv;
347 }
348 else if (tag == "VV4F") {
349 tagType = ::Value::tag::VV4F;
350 std::shared_ptr<data::VV4F> tv(new data::VV4F());
351 tv->_0 = fromJSON(W<V4F>(), obj["arg0"]);
352 return tv;
353 }
354 else if (tag == "VM22F") {
355 tagType = ::Value::tag::VM22F;
356 std::shared_ptr<data::VM22F> tv(new data::VM22F());
357 tv->_0 = fromJSON(W<M22F>(), obj["arg0"]);
358 return tv;
359 }
360 else if (tag == "VM23F") {
361 tagType = ::Value::tag::VM23F;
362 std::shared_ptr<data::VM23F> tv(new data::VM23F());
363 tv->_0 = fromJSON(W<M23F>(), obj["arg0"]);
364 return tv;
365 }
366 else if (tag == "VM24F") {
367 tagType = ::Value::tag::VM24F;
368 std::shared_ptr<data::VM24F> tv(new data::VM24F());
369 tv->_0 = fromJSON(W<M24F>(), obj["arg0"]);
370 return tv;
371 }
372 else if (tag == "VM32F") {
373 tagType = ::Value::tag::VM32F;
374 std::shared_ptr<data::VM32F> tv(new data::VM32F());
375 tv->_0 = fromJSON(W<M32F>(), obj["arg0"]);
376 return tv;
377 }
378 else if (tag == "VM33F") {
379 tagType = ::Value::tag::VM33F;
380 std::shared_ptr<data::VM33F> tv(new data::VM33F());
381 tv->_0 = fromJSON(W<M33F>(), obj["arg0"]);
382 return tv;
383 }
384 else if (tag == "VM34F") {
385 tagType = ::Value::tag::VM34F;
386 std::shared_ptr<data::VM34F> tv(new data::VM34F());
387 tv->_0 = fromJSON(W<M34F>(), obj["arg0"]);
388 return tv;
389 }
390 else if (tag == "VM42F") {
391 tagType = ::Value::tag::VM42F;
392 std::shared_ptr<data::VM42F> tv(new data::VM42F());
393 tv->_0 = fromJSON(W<M42F>(), obj["arg0"]);
394 return tv;
395 }
396 else if (tag == "VM43F") {
397 tagType = ::Value::tag::VM43F;
398 std::shared_ptr<data::VM43F> tv(new data::VM43F());
399 tv->_0 = fromJSON(W<M43F>(), obj["arg0"]);
400 return tv;
401 }
402 else if (tag == "VM44F") {
403 tagType = ::Value::tag::VM44F;
404 std::shared_ptr<data::VM44F> tv(new data::VM44F());
405 tv->_0 = fromJSON(W<M44F>(), obj["arg0"]);
406 return tv;
407 }
408 else throw "unknown constructor: " + tag;
409 std::shared_ptr<::Value> o(new ::Value());
410 o->tag = tagType;
411 return o;
412}
413
414template<> json toJSON<std::shared_ptr<InputType>>(std::shared_ptr<InputType> &v) {
415 json obj({});
416 switch (v->tag) {
417 case ::InputType::tag::Bool:
418 obj["tag"] = "Bool";
419 break;
420 case ::InputType::tag::V2B:
421 obj["tag"] = "V2B";
422 break;
423 case ::InputType::tag::V3B:
424 obj["tag"] = "V3B";
425 break;
426 case ::InputType::tag::V4B:
427 obj["tag"] = "V4B";
428 break;
429 case ::InputType::tag::Word:
430 obj["tag"] = "Word";
431 break;
432 case ::InputType::tag::V2U:
433 obj["tag"] = "V2U";
434 break;
435 case ::InputType::tag::V3U:
436 obj["tag"] = "V3U";
437 break;
438 case ::InputType::tag::V4U:
439 obj["tag"] = "V4U";
440 break;
441 case ::InputType::tag::Int:
442 obj["tag"] = "Int";
443 break;
444 case ::InputType::tag::V2I:
445 obj["tag"] = "V2I";
446 break;
447 case ::InputType::tag::V3I:
448 obj["tag"] = "V3I";
449 break;
450 case ::InputType::tag::V4I:
451 obj["tag"] = "V4I";
452 break;
453 case ::InputType::tag::Float:
454 obj["tag"] = "Float";
455 break;
456 case ::InputType::tag::V2F:
457 obj["tag"] = "V2F";
458 break;
459 case ::InputType::tag::V3F:
460 obj["tag"] = "V3F";
461 break;
462 case ::InputType::tag::V4F:
463 obj["tag"] = "V4F";
464 break;
465 case ::InputType::tag::M22F:
466 obj["tag"] = "M22F";
467 break;
468 case ::InputType::tag::M23F:
469 obj["tag"] = "M23F";
470 break;
471 case ::InputType::tag::M24F:
472 obj["tag"] = "M24F";
473 break;
474 case ::InputType::tag::M32F:
475 obj["tag"] = "M32F";
476 break;
477 case ::InputType::tag::M33F:
478 obj["tag"] = "M33F";
479 break;
480 case ::InputType::tag::M34F:
481 obj["tag"] = "M34F";
482 break;
483 case ::InputType::tag::M42F:
484 obj["tag"] = "M42F";
485 break;
486 case ::InputType::tag::M43F:
487 obj["tag"] = "M43F";
488 break;
489 case ::InputType::tag::M44F:
490 obj["tag"] = "M44F";
491 break;
492 case ::InputType::tag::STexture1D:
493 obj["tag"] = "STexture1D";
494 break;
495 case ::InputType::tag::STexture2D:
496 obj["tag"] = "STexture2D";
497 break;
498 case ::InputType::tag::STextureCube:
499 obj["tag"] = "STextureCube";
500 break;
501 case ::InputType::tag::STexture1DArray:
502 obj["tag"] = "STexture1DArray";
503 break;
504 case ::InputType::tag::STexture2DArray:
505 obj["tag"] = "STexture2DArray";
506 break;
507 case ::InputType::tag::STexture2DRect:
508 obj["tag"] = "STexture2DRect";
509 break;
510 case ::InputType::tag::FTexture1D:
511 obj["tag"] = "FTexture1D";
512 break;
513 case ::InputType::tag::FTexture2D:
514 obj["tag"] = "FTexture2D";
515 break;
516 case ::InputType::tag::FTexture3D:
517 obj["tag"] = "FTexture3D";
518 break;
519 case ::InputType::tag::FTextureCube:
520 obj["tag"] = "FTextureCube";
521 break;
522 case ::InputType::tag::FTexture1DArray:
523 obj["tag"] = "FTexture1DArray";
524 break;
525 case ::InputType::tag::FTexture2DArray:
526 obj["tag"] = "FTexture2DArray";
527 break;
528 case ::InputType::tag::FTexture2DMS:
529 obj["tag"] = "FTexture2DMS";
530 break;
531 case ::InputType::tag::FTexture2DMSArray:
532 obj["tag"] = "FTexture2DMSArray";
533 break;
534 case ::InputType::tag::FTextureBuffer:
535 obj["tag"] = "FTextureBuffer";
536 break;
537 case ::InputType::tag::FTexture2DRect:
538 obj["tag"] = "FTexture2DRect";
539 break;
540 case ::InputType::tag::ITexture1D:
541 obj["tag"] = "ITexture1D";
542 break;
543 case ::InputType::tag::ITexture2D:
544 obj["tag"] = "ITexture2D";
545 break;
546 case ::InputType::tag::ITexture3D:
547 obj["tag"] = "ITexture3D";
548 break;
549 case ::InputType::tag::ITextureCube:
550 obj["tag"] = "ITextureCube";
551 break;
552 case ::InputType::tag::ITexture1DArray:
553 obj["tag"] = "ITexture1DArray";
554 break;
555 case ::InputType::tag::ITexture2DArray:
556 obj["tag"] = "ITexture2DArray";
557 break;
558 case ::InputType::tag::ITexture2DMS:
559 obj["tag"] = "ITexture2DMS";
560 break;
561 case ::InputType::tag::ITexture2DMSArray:
562 obj["tag"] = "ITexture2DMSArray";
563 break;
564 case ::InputType::tag::ITextureBuffer:
565 obj["tag"] = "ITextureBuffer";
566 break;
567 case ::InputType::tag::ITexture2DRect:
568 obj["tag"] = "ITexture2DRect";
569 break;
570 case ::InputType::tag::UTexture1D:
571 obj["tag"] = "UTexture1D";
572 break;
573 case ::InputType::tag::UTexture2D:
574 obj["tag"] = "UTexture2D";
575 break;
576 case ::InputType::tag::UTexture3D:
577 obj["tag"] = "UTexture3D";
578 break;
579 case ::InputType::tag::UTextureCube:
580 obj["tag"] = "UTextureCube";
581 break;
582 case ::InputType::tag::UTexture1DArray:
583 obj["tag"] = "UTexture1DArray";
584 break;
585 case ::InputType::tag::UTexture2DArray:
586 obj["tag"] = "UTexture2DArray";
587 break;
588 case ::InputType::tag::UTexture2DMS:
589 obj["tag"] = "UTexture2DMS";
590 break;
591 case ::InputType::tag::UTexture2DMSArray:
592 obj["tag"] = "UTexture2DMSArray";
593 break;
594 case ::InputType::tag::UTextureBuffer:
595 obj["tag"] = "UTextureBuffer";
596 break;
597 case ::InputType::tag::UTexture2DRect:
598 obj["tag"] = "UTexture2DRect";
599 break;
600 }
601 return obj;
602}
603
604template<> std::shared_ptr<InputType> fromJSON<std::shared_ptr<InputType>>(W<std::shared_ptr<InputType>> v, json &obj) {
605 enum ::InputType::tag tagType;
606 std::string tag = obj["tag"];
607 if (tag == "Bool") {
608 tagType = ::InputType::tag::Bool;
609 }
610 else if (tag == "V2B") {
611 tagType = ::InputType::tag::V2B;
612 }
613 else if (tag == "V3B") {
614 tagType = ::InputType::tag::V3B;
615 }
616 else if (tag == "V4B") {
617 tagType = ::InputType::tag::V4B;
618 }
619 else if (tag == "Word") {
620 tagType = ::InputType::tag::Word;
621 }
622 else if (tag == "V2U") {
623 tagType = ::InputType::tag::V2U;
624 }
625 else if (tag == "V3U") {
626 tagType = ::InputType::tag::V3U;
627 }
628 else if (tag == "V4U") {
629 tagType = ::InputType::tag::V4U;
630 }
631 else if (tag == "Int") {
632 tagType = ::InputType::tag::Int;
633 }
634 else if (tag == "V2I") {
635 tagType = ::InputType::tag::V2I;
636 }
637 else if (tag == "V3I") {
638 tagType = ::InputType::tag::V3I;
639 }
640 else if (tag == "V4I") {
641 tagType = ::InputType::tag::V4I;
642 }
643 else if (tag == "Float") {
644 tagType = ::InputType::tag::Float;
645 }
646 else if (tag == "V2F") {
647 tagType = ::InputType::tag::V2F;
648 }
649 else if (tag == "V3F") {
650 tagType = ::InputType::tag::V3F;
651 }
652 else if (tag == "V4F") {
653 tagType = ::InputType::tag::V4F;
654 }
655 else if (tag == "M22F") {
656 tagType = ::InputType::tag::M22F;
657 }
658 else if (tag == "M23F") {
659 tagType = ::InputType::tag::M23F;
660 }
661 else if (tag == "M24F") {
662 tagType = ::InputType::tag::M24F;
663 }
664 else if (tag == "M32F") {
665 tagType = ::InputType::tag::M32F;
666 }
667 else if (tag == "M33F") {
668 tagType = ::InputType::tag::M33F;
669 }
670 else if (tag == "M34F") {
671 tagType = ::InputType::tag::M34F;
672 }
673 else if (tag == "M42F") {
674 tagType = ::InputType::tag::M42F;
675 }
676 else if (tag == "M43F") {
677 tagType = ::InputType::tag::M43F;
678 }
679 else if (tag == "M44F") {
680 tagType = ::InputType::tag::M44F;
681 }
682 else if (tag == "STexture1D") {
683 tagType = ::InputType::tag::STexture1D;
684 }
685 else if (tag == "STexture2D") {
686 tagType = ::InputType::tag::STexture2D;
687 }
688 else if (tag == "STextureCube") {
689 tagType = ::InputType::tag::STextureCube;
690 }
691 else if (tag == "STexture1DArray") {
692 tagType = ::InputType::tag::STexture1DArray;
693 }
694 else if (tag == "STexture2DArray") {
695 tagType = ::InputType::tag::STexture2DArray;
696 }
697 else if (tag == "STexture2DRect") {
698 tagType = ::InputType::tag::STexture2DRect;
699 }
700 else if (tag == "FTexture1D") {
701 tagType = ::InputType::tag::FTexture1D;
702 }
703 else if (tag == "FTexture2D") {
704 tagType = ::InputType::tag::FTexture2D;
705 }
706 else if (tag == "FTexture3D") {
707 tagType = ::InputType::tag::FTexture3D;
708 }
709 else if (tag == "FTextureCube") {
710 tagType = ::InputType::tag::FTextureCube;
711 }
712 else if (tag == "FTexture1DArray") {
713 tagType = ::InputType::tag::FTexture1DArray;
714 }
715 else if (tag == "FTexture2DArray") {
716 tagType = ::InputType::tag::FTexture2DArray;
717 }
718 else if (tag == "FTexture2DMS") {
719 tagType = ::InputType::tag::FTexture2DMS;
720 }
721 else if (tag == "FTexture2DMSArray") {
722 tagType = ::InputType::tag::FTexture2DMSArray;
723 }
724 else if (tag == "FTextureBuffer") {
725 tagType = ::InputType::tag::FTextureBuffer;
726 }
727 else if (tag == "FTexture2DRect") {
728 tagType = ::InputType::tag::FTexture2DRect;
729 }
730 else if (tag == "ITexture1D") {
731 tagType = ::InputType::tag::ITexture1D;
732 }
733 else if (tag == "ITexture2D") {
734 tagType = ::InputType::tag::ITexture2D;
735 }
736 else if (tag == "ITexture3D") {
737 tagType = ::InputType::tag::ITexture3D;
738 }
739 else if (tag == "ITextureCube") {
740 tagType = ::InputType::tag::ITextureCube;
741 }
742 else if (tag == "ITexture1DArray") {
743 tagType = ::InputType::tag::ITexture1DArray;
744 }
745 else if (tag == "ITexture2DArray") {
746 tagType = ::InputType::tag::ITexture2DArray;
747 }
748 else if (tag == "ITexture2DMS") {
749 tagType = ::InputType::tag::ITexture2DMS;
750 }
751 else if (tag == "ITexture2DMSArray") {
752 tagType = ::InputType::tag::ITexture2DMSArray;
753 }
754 else if (tag == "ITextureBuffer") {
755 tagType = ::InputType::tag::ITextureBuffer;
756 }
757 else if (tag == "ITexture2DRect") {
758 tagType = ::InputType::tag::ITexture2DRect;
759 }
760 else if (tag == "UTexture1D") {
761 tagType = ::InputType::tag::UTexture1D;
762 }
763 else if (tag == "UTexture2D") {
764 tagType = ::InputType::tag::UTexture2D;
765 }
766 else if (tag == "UTexture3D") {
767 tagType = ::InputType::tag::UTexture3D;
768 }
769 else if (tag == "UTextureCube") {
770 tagType = ::InputType::tag::UTextureCube;
771 }
772 else if (tag == "UTexture1DArray") {
773 tagType = ::InputType::tag::UTexture1DArray;
774 }
775 else if (tag == "UTexture2DArray") {
776 tagType = ::InputType::tag::UTexture2DArray;
777 }
778 else if (tag == "UTexture2DMS") {
779 tagType = ::InputType::tag::UTexture2DMS;
780 }
781 else if (tag == "UTexture2DMSArray") {
782 tagType = ::InputType::tag::UTexture2DMSArray;
783 }
784 else if (tag == "UTextureBuffer") {
785 tagType = ::InputType::tag::UTextureBuffer;
786 }
787 else if (tag == "UTexture2DRect") {
788 tagType = ::InputType::tag::UTexture2DRect;
789 }
790 else throw "unknown constructor: " + tag;
791 std::shared_ptr<::InputType> o(new ::InputType());
792 o->tag = tagType;
793 return o;
794}
795
796template<> json toJSON<std::shared_ptr<PointSpriteCoordOrigin>>(std::shared_ptr<PointSpriteCoordOrigin> &v) {
797 json obj({});
798 switch (v->tag) {
799 case ::PointSpriteCoordOrigin::tag::LowerLeft:
800 obj["tag"] = "LowerLeft";
801 break;
802 case ::PointSpriteCoordOrigin::tag::UpperLeft:
803 obj["tag"] = "UpperLeft";
804 break;
805 }
806 return obj;
807}
808
809template<> std::shared_ptr<PointSpriteCoordOrigin> fromJSON<std::shared_ptr<PointSpriteCoordOrigin>>(W<std::shared_ptr<PointSpriteCoordOrigin>> v, json &obj) {
810 enum ::PointSpriteCoordOrigin::tag tagType;
811 std::string tag = obj["tag"];
812 if (tag == "LowerLeft") {
813 tagType = ::PointSpriteCoordOrigin::tag::LowerLeft;
814 }
815 else if (tag == "UpperLeft") {
816 tagType = ::PointSpriteCoordOrigin::tag::UpperLeft;
817 }
818 else throw "unknown constructor: " + tag;
819 std::shared_ptr<::PointSpriteCoordOrigin> o(new ::PointSpriteCoordOrigin());
820 o->tag = tagType;
821 return o;
822}
823
824template<> json toJSON<std::shared_ptr<PointSize>>(std::shared_ptr<PointSize> &v) {
825 json obj({});
826 switch (v->tag) {
827 case ::PointSize::tag::PointSize:
828 obj["tag"] = "PointSize";
829 {
830 std::shared_ptr<data::PointSize> tv = std::static_pointer_cast<data::PointSize>(v);
831 obj["arg0"] = toJSON(tv->_0);
832 }
833 break;
834 case ::PointSize::tag::ProgramPointSize:
835 obj["tag"] = "ProgramPointSize";
836 break;
837 }
838 return obj;
839}
840
841template<> std::shared_ptr<PointSize> fromJSON<std::shared_ptr<PointSize>>(W<std::shared_ptr<PointSize>> v, json &obj) {
842 enum ::PointSize::tag tagType;
843 std::string tag = obj["tag"];
844 if (tag == "PointSize") {
845 tagType = ::PointSize::tag::PointSize;
846 std::shared_ptr<data::PointSize> tv(new data::PointSize());
847 tv->_0 = fromJSON(W<Float>(), obj["arg0"]);
848 return tv;
849 }
850 else if (tag == "ProgramPointSize") {
851 tagType = ::PointSize::tag::ProgramPointSize;
852 }
853 else throw "unknown constructor: " + tag;
854 std::shared_ptr<::PointSize> o(new ::PointSize());
855 o->tag = tagType;
856 return o;
857}
858
859template<> json toJSON<std::shared_ptr<PolygonOffset>>(std::shared_ptr<PolygonOffset> &v) {
860 json obj({});
861 switch (v->tag) {
862 case ::PolygonOffset::tag::NoOffset:
863 obj["tag"] = "NoOffset";
864 break;
865 case ::PolygonOffset::tag::Offset:
866 obj["tag"] = "Offset";
867 {
868 std::shared_ptr<data::Offset> tv = std::static_pointer_cast<data::Offset>(v);
869 obj["arg0"] = toJSON(tv->_0);
870 obj["arg1"] = toJSON(tv->_1);
871 }
872 break;
873 }
874 return obj;
875}
876
877template<> std::shared_ptr<PolygonOffset> fromJSON<std::shared_ptr<PolygonOffset>>(W<std::shared_ptr<PolygonOffset>> v, json &obj) {
878 enum ::PolygonOffset::tag tagType;
879 std::string tag = obj["tag"];
880 if (tag == "NoOffset") {
881 tagType = ::PolygonOffset::tag::NoOffset;
882 }
883 else if (tag == "Offset") {
884 tagType = ::PolygonOffset::tag::Offset;
885 std::shared_ptr<data::Offset> tv(new data::Offset());
886 tv->_0 = fromJSON(W<Float>(), obj["arg0"]);
887 tv->_1 = fromJSON(W<Float>(), obj["arg1"]);
888 return tv;
889 }
890 else throw "unknown constructor: " + tag;
891 std::shared_ptr<::PolygonOffset> o(new ::PolygonOffset());
892 o->tag = tagType;
893 return o;
894}
895
896template<> json toJSON<std::shared_ptr<FrontFace>>(std::shared_ptr<FrontFace> &v) {
897 json obj({});
898 switch (v->tag) {
899 case ::FrontFace::tag::CCW:
900 obj["tag"] = "CCW";
901 break;
902 case ::FrontFace::tag::CW:
903 obj["tag"] = "CW";
904 break;
905 }
906 return obj;
907}
908
909template<> std::shared_ptr<FrontFace> fromJSON<std::shared_ptr<FrontFace>>(W<std::shared_ptr<FrontFace>> v, json &obj) {
910 enum ::FrontFace::tag tagType;
911 std::string tag = obj["tag"];
912 if (tag == "CCW") {
913 tagType = ::FrontFace::tag::CCW;
914 }
915 else if (tag == "CW") {
916 tagType = ::FrontFace::tag::CW;
917 }
918 else throw "unknown constructor: " + tag;
919 std::shared_ptr<::FrontFace> o(new ::FrontFace());
920 o->tag = tagType;
921 return o;
922}
923
924template<> json toJSON<std::shared_ptr<PolygonMode>>(std::shared_ptr<PolygonMode> &v) {
925 json obj({});
926 switch (v->tag) {
927 case ::PolygonMode::tag::PolygonPoint:
928 obj["tag"] = "PolygonPoint";
929 {
930 std::shared_ptr<data::PolygonPoint> tv = std::static_pointer_cast<data::PolygonPoint>(v);
931 obj["arg0"] = toJSON(tv->_0);
932 }
933 break;
934 case ::PolygonMode::tag::PolygonLine:
935 obj["tag"] = "PolygonLine";
936 {
937 std::shared_ptr<data::PolygonLine> tv = std::static_pointer_cast<data::PolygonLine>(v);
938 obj["arg0"] = toJSON(tv->_0);
939 }
940 break;
941 case ::PolygonMode::tag::PolygonFill:
942 obj["tag"] = "PolygonFill";
943 break;
944 }
945 return obj;
946}
947
948template<> std::shared_ptr<PolygonMode> fromJSON<std::shared_ptr<PolygonMode>>(W<std::shared_ptr<PolygonMode>> v, json &obj) {
949 enum ::PolygonMode::tag tagType;
950 std::string tag = obj["tag"];
951 if (tag == "PolygonPoint") {
952 tagType = ::PolygonMode::tag::PolygonPoint;
953 std::shared_ptr<data::PolygonPoint> tv(new data::PolygonPoint());
954 tv->_0 = fromJSON(W<std::shared_ptr<::PointSize>>(), obj["arg0"]);
955 return tv;
956 }
957 else if (tag == "PolygonLine") {
958 tagType = ::PolygonMode::tag::PolygonLine;
959 std::shared_ptr<data::PolygonLine> tv(new data::PolygonLine());
960 tv->_0 = fromJSON(W<Float>(), obj["arg0"]);
961 return tv;
962 }
963 else if (tag == "PolygonFill") {
964 tagType = ::PolygonMode::tag::PolygonFill;
965 }
966 else throw "unknown constructor: " + tag;
967 std::shared_ptr<::PolygonMode> o(new ::PolygonMode());
968 o->tag = tagType;
969 return o;
970}
971
972template<> json toJSON<std::shared_ptr<ProvokingVertex>>(std::shared_ptr<ProvokingVertex> &v) {
973 json obj({});
974 switch (v->tag) {
975 case ::ProvokingVertex::tag::FirstVertex:
976 obj["tag"] = "FirstVertex";
977 break;
978 case ::ProvokingVertex::tag::LastVertex:
979 obj["tag"] = "LastVertex";
980 break;
981 }
982 return obj;
983}
984
985template<> std::shared_ptr<ProvokingVertex> fromJSON<std::shared_ptr<ProvokingVertex>>(W<std::shared_ptr<ProvokingVertex>> v, json &obj) {
986 enum ::ProvokingVertex::tag tagType;
987 std::string tag = obj["tag"];
988 if (tag == "FirstVertex") {
989 tagType = ::ProvokingVertex::tag::FirstVertex;
990 }
991 else if (tag == "LastVertex") {
992 tagType = ::ProvokingVertex::tag::LastVertex;
993 }
994 else throw "unknown constructor: " + tag;
995 std::shared_ptr<::ProvokingVertex> o(new ::ProvokingVertex());
996 o->tag = tagType;
997 return o;
998}
999
1000template<> json toJSON<std::shared_ptr<CullMode>>(std::shared_ptr<CullMode> &v) {
1001 json obj({});
1002 switch (v->tag) {
1003 case ::CullMode::tag::CullNone:
1004 obj["tag"] = "CullNone";
1005 break;
1006 case ::CullMode::tag::CullFront:
1007 obj["tag"] = "CullFront";
1008 {
1009 std::shared_ptr<data::CullFront> tv = std::static_pointer_cast<data::CullFront>(v);
1010 obj["arg0"] = toJSON(tv->_0);
1011 }
1012 break;
1013 case ::CullMode::tag::CullBack:
1014 obj["tag"] = "CullBack";
1015 {
1016 std::shared_ptr<data::CullBack> tv = std::static_pointer_cast<data::CullBack>(v);
1017 obj["arg0"] = toJSON(tv->_0);
1018 }
1019 break;
1020 }
1021 return obj;
1022}
1023
1024template<> std::shared_ptr<CullMode> fromJSON<std::shared_ptr<CullMode>>(W<std::shared_ptr<CullMode>> v, json &obj) {
1025 enum ::CullMode::tag tagType;
1026 std::string tag = obj["tag"];
1027 if (tag == "CullNone") {
1028 tagType = ::CullMode::tag::CullNone;
1029 }
1030 else if (tag == "CullFront") {
1031 tagType = ::CullMode::tag::CullFront;
1032 std::shared_ptr<data::CullFront> tv(new data::CullFront());
1033 tv->_0 = fromJSON(W<std::shared_ptr<::FrontFace>>(), obj["arg0"]);
1034 return tv;
1035 }
1036 else if (tag == "CullBack") {
1037 tagType = ::CullMode::tag::CullBack;
1038 std::shared_ptr<data::CullBack> tv(new data::CullBack());
1039 tv->_0 = fromJSON(W<std::shared_ptr<::FrontFace>>(), obj["arg0"]);
1040 return tv;
1041 }
1042 else throw "unknown constructor: " + tag;
1043 std::shared_ptr<::CullMode> o(new ::CullMode());
1044 o->tag = tagType;
1045 return o;
1046}
1047
1048template<> json toJSON<std::shared_ptr<ComparisonFunction>>(std::shared_ptr<ComparisonFunction> &v) {
1049 json obj({});
1050 switch (v->tag) {
1051 case ::ComparisonFunction::tag::Never:
1052 obj["tag"] = "Never";
1053 break;
1054 case ::ComparisonFunction::tag::Less:
1055 obj["tag"] = "Less";
1056 break;
1057 case ::ComparisonFunction::tag::Equal:
1058 obj["tag"] = "Equal";
1059 break;
1060 case ::ComparisonFunction::tag::Lequal:
1061 obj["tag"] = "Lequal";
1062 break;
1063 case ::ComparisonFunction::tag::Greater:
1064 obj["tag"] = "Greater";
1065 break;
1066 case ::ComparisonFunction::tag::Notequal:
1067 obj["tag"] = "Notequal";
1068 break;
1069 case ::ComparisonFunction::tag::Gequal:
1070 obj["tag"] = "Gequal";
1071 break;
1072 case ::ComparisonFunction::tag::Always:
1073 obj["tag"] = "Always";
1074 break;
1075 }
1076 return obj;
1077}
1078
1079template<> std::shared_ptr<ComparisonFunction> fromJSON<std::shared_ptr<ComparisonFunction>>(W<std::shared_ptr<ComparisonFunction>> v, json &obj) {
1080 enum ::ComparisonFunction::tag tagType;
1081 std::string tag = obj["tag"];
1082 if (tag == "Never") {
1083 tagType = ::ComparisonFunction::tag::Never;
1084 }
1085 else if (tag == "Less") {
1086 tagType = ::ComparisonFunction::tag::Less;
1087 }
1088 else if (tag == "Equal") {
1089 tagType = ::ComparisonFunction::tag::Equal;
1090 }
1091 else if (tag == "Lequal") {
1092 tagType = ::ComparisonFunction::tag::Lequal;
1093 }
1094 else if (tag == "Greater") {
1095 tagType = ::ComparisonFunction::tag::Greater;
1096 }
1097 else if (tag == "Notequal") {
1098 tagType = ::ComparisonFunction::tag::Notequal;
1099 }
1100 else if (tag == "Gequal") {
1101 tagType = ::ComparisonFunction::tag::Gequal;
1102 }
1103 else if (tag == "Always") {
1104 tagType = ::ComparisonFunction::tag::Always;
1105 }
1106 else throw "unknown constructor: " + tag;
1107 std::shared_ptr<::ComparisonFunction> o(new ::ComparisonFunction());
1108 o->tag = tagType;
1109 return o;
1110}
1111
1112template<> json toJSON<std::shared_ptr<StencilOperation>>(std::shared_ptr<StencilOperation> &v) {
1113 json obj({});
1114 switch (v->tag) {
1115 case ::StencilOperation::tag::OpZero:
1116 obj["tag"] = "OpZero";
1117 break;
1118 case ::StencilOperation::tag::OpKeep:
1119 obj["tag"] = "OpKeep";
1120 break;
1121 case ::StencilOperation::tag::OpReplace:
1122 obj["tag"] = "OpReplace";
1123 break;
1124 case ::StencilOperation::tag::OpIncr:
1125 obj["tag"] = "OpIncr";
1126 break;
1127 case ::StencilOperation::tag::OpIncrWrap:
1128 obj["tag"] = "OpIncrWrap";
1129 break;
1130 case ::StencilOperation::tag::OpDecr:
1131 obj["tag"] = "OpDecr";
1132 break;
1133 case ::StencilOperation::tag::OpDecrWrap:
1134 obj["tag"] = "OpDecrWrap";
1135 break;
1136 case ::StencilOperation::tag::OpInvert:
1137 obj["tag"] = "OpInvert";
1138 break;
1139 }
1140 return obj;
1141}
1142
1143template<> std::shared_ptr<StencilOperation> fromJSON<std::shared_ptr<StencilOperation>>(W<std::shared_ptr<StencilOperation>> v, json &obj) {
1144 enum ::StencilOperation::tag tagType;
1145 std::string tag = obj["tag"];
1146 if (tag == "OpZero") {
1147 tagType = ::StencilOperation::tag::OpZero;
1148 }
1149 else if (tag == "OpKeep") {
1150 tagType = ::StencilOperation::tag::OpKeep;
1151 }
1152 else if (tag == "OpReplace") {
1153 tagType = ::StencilOperation::tag::OpReplace;
1154 }
1155 else if (tag == "OpIncr") {
1156 tagType = ::StencilOperation::tag::OpIncr;
1157 }
1158 else if (tag == "OpIncrWrap") {
1159 tagType = ::StencilOperation::tag::OpIncrWrap;
1160 }
1161 else if (tag == "OpDecr") {
1162 tagType = ::StencilOperation::tag::OpDecr;
1163 }
1164 else if (tag == "OpDecrWrap") {
1165 tagType = ::StencilOperation::tag::OpDecrWrap;
1166 }
1167 else if (tag == "OpInvert") {
1168 tagType = ::StencilOperation::tag::OpInvert;
1169 }
1170 else throw "unknown constructor: " + tag;
1171 std::shared_ptr<::StencilOperation> o(new ::StencilOperation());
1172 o->tag = tagType;
1173 return o;
1174}
1175
1176template<> json toJSON<std::shared_ptr<BlendEquation>>(std::shared_ptr<BlendEquation> &v) {
1177 json obj({});
1178 switch (v->tag) {
1179 case ::BlendEquation::tag::FuncAdd:
1180 obj["tag"] = "FuncAdd";
1181 break;
1182 case ::BlendEquation::tag::FuncSubtract:
1183 obj["tag"] = "FuncSubtract";
1184 break;
1185 case ::BlendEquation::tag::FuncReverseSubtract:
1186 obj["tag"] = "FuncReverseSubtract";
1187 break;
1188 case ::BlendEquation::tag::Min:
1189 obj["tag"] = "Min";
1190 break;
1191 case ::BlendEquation::tag::Max:
1192 obj["tag"] = "Max";
1193 break;
1194 }
1195 return obj;
1196}
1197
1198template<> std::shared_ptr<BlendEquation> fromJSON<std::shared_ptr<BlendEquation>>(W<std::shared_ptr<BlendEquation>> v, json &obj) {
1199 enum ::BlendEquation::tag tagType;
1200 std::string tag = obj["tag"];
1201 if (tag == "FuncAdd") {
1202 tagType = ::BlendEquation::tag::FuncAdd;
1203 }
1204 else if (tag == "FuncSubtract") {
1205 tagType = ::BlendEquation::tag::FuncSubtract;
1206 }
1207 else if (tag == "FuncReverseSubtract") {
1208 tagType = ::BlendEquation::tag::FuncReverseSubtract;
1209 }
1210 else if (tag == "Min") {
1211 tagType = ::BlendEquation::tag::Min;
1212 }
1213 else if (tag == "Max") {
1214 tagType = ::BlendEquation::tag::Max;
1215 }
1216 else throw "unknown constructor: " + tag;
1217 std::shared_ptr<::BlendEquation> o(new ::BlendEquation());
1218 o->tag = tagType;
1219 return o;
1220}
1221
1222template<> json toJSON<std::shared_ptr<BlendingFactor>>(std::shared_ptr<BlendingFactor> &v) {
1223 json obj({});
1224 switch (v->tag) {
1225 case ::BlendingFactor::tag::Zero:
1226 obj["tag"] = "Zero";
1227 break;
1228 case ::BlendingFactor::tag::One:
1229 obj["tag"] = "One";
1230 break;
1231 case ::BlendingFactor::tag::SrcColor:
1232 obj["tag"] = "SrcColor";
1233 break;
1234 case ::BlendingFactor::tag::OneMinusSrcColor:
1235 obj["tag"] = "OneMinusSrcColor";
1236 break;
1237 case ::BlendingFactor::tag::DstColor:
1238 obj["tag"] = "DstColor";
1239 break;
1240 case ::BlendingFactor::tag::OneMinusDstColor:
1241 obj["tag"] = "OneMinusDstColor";
1242 break;
1243 case ::BlendingFactor::tag::SrcAlpha:
1244 obj["tag"] = "SrcAlpha";
1245 break;
1246 case ::BlendingFactor::tag::OneMinusSrcAlpha:
1247 obj["tag"] = "OneMinusSrcAlpha";
1248 break;
1249 case ::BlendingFactor::tag::DstAlpha:
1250 obj["tag"] = "DstAlpha";
1251 break;
1252 case ::BlendingFactor::tag::OneMinusDstAlpha:
1253 obj["tag"] = "OneMinusDstAlpha";
1254 break;
1255 case ::BlendingFactor::tag::ConstantColor:
1256 obj["tag"] = "ConstantColor";
1257 break;
1258 case ::BlendingFactor::tag::OneMinusConstantColor:
1259 obj["tag"] = "OneMinusConstantColor";
1260 break;
1261 case ::BlendingFactor::tag::ConstantAlpha:
1262 obj["tag"] = "ConstantAlpha";
1263 break;
1264 case ::BlendingFactor::tag::OneMinusConstantAlpha:
1265 obj["tag"] = "OneMinusConstantAlpha";
1266 break;
1267 case ::BlendingFactor::tag::SrcAlphaSaturate:
1268 obj["tag"] = "SrcAlphaSaturate";
1269 break;
1270 }
1271 return obj;
1272}
1273
1274template<> std::shared_ptr<BlendingFactor> fromJSON<std::shared_ptr<BlendingFactor>>(W<std::shared_ptr<BlendingFactor>> v, json &obj) {
1275 enum ::BlendingFactor::tag tagType;
1276 std::string tag = obj["tag"];
1277 if (tag == "Zero") {
1278 tagType = ::BlendingFactor::tag::Zero;
1279 }
1280 else if (tag == "One") {
1281 tagType = ::BlendingFactor::tag::One;
1282 }
1283 else if (tag == "SrcColor") {
1284 tagType = ::BlendingFactor::tag::SrcColor;
1285 }
1286 else if (tag == "OneMinusSrcColor") {
1287 tagType = ::BlendingFactor::tag::OneMinusSrcColor;
1288 }
1289 else if (tag == "DstColor") {
1290 tagType = ::BlendingFactor::tag::DstColor;
1291 }
1292 else if (tag == "OneMinusDstColor") {
1293 tagType = ::BlendingFactor::tag::OneMinusDstColor;
1294 }
1295 else if (tag == "SrcAlpha") {
1296 tagType = ::BlendingFactor::tag::SrcAlpha;
1297 }
1298 else if (tag == "OneMinusSrcAlpha") {
1299 tagType = ::BlendingFactor::tag::OneMinusSrcAlpha;
1300 }
1301 else if (tag == "DstAlpha") {
1302 tagType = ::BlendingFactor::tag::DstAlpha;
1303 }
1304 else if (tag == "OneMinusDstAlpha") {
1305 tagType = ::BlendingFactor::tag::OneMinusDstAlpha;
1306 }
1307 else if (tag == "ConstantColor") {
1308 tagType = ::BlendingFactor::tag::ConstantColor;
1309 }
1310 else if (tag == "OneMinusConstantColor") {
1311 tagType = ::BlendingFactor::tag::OneMinusConstantColor;
1312 }
1313 else if (tag == "ConstantAlpha") {
1314 tagType = ::BlendingFactor::tag::ConstantAlpha;
1315 }
1316 else if (tag == "OneMinusConstantAlpha") {
1317 tagType = ::BlendingFactor::tag::OneMinusConstantAlpha;
1318 }
1319 else if (tag == "SrcAlphaSaturate") {
1320 tagType = ::BlendingFactor::tag::SrcAlphaSaturate;
1321 }
1322 else throw "unknown constructor: " + tag;
1323 std::shared_ptr<::BlendingFactor> o(new ::BlendingFactor());
1324 o->tag = tagType;
1325 return o;
1326}
1327
1328template<> json toJSON<std::shared_ptr<LogicOperation>>(std::shared_ptr<LogicOperation> &v) {
1329 json obj({});
1330 switch (v->tag) {
1331 case ::LogicOperation::tag::Clear:
1332 obj["tag"] = "Clear";
1333 break;
1334 case ::LogicOperation::tag::And:
1335 obj["tag"] = "And";
1336 break;
1337 case ::LogicOperation::tag::AndReverse:
1338 obj["tag"] = "AndReverse";
1339 break;
1340 case ::LogicOperation::tag::Copy:
1341 obj["tag"] = "Copy";
1342 break;
1343 case ::LogicOperation::tag::AndInverted:
1344 obj["tag"] = "AndInverted";
1345 break;
1346 case ::LogicOperation::tag::Noop:
1347 obj["tag"] = "Noop";
1348 break;
1349 case ::LogicOperation::tag::Xor:
1350 obj["tag"] = "Xor";
1351 break;
1352 case ::LogicOperation::tag::Or:
1353 obj["tag"] = "Or";
1354 break;
1355 case ::LogicOperation::tag::Nor:
1356 obj["tag"] = "Nor";
1357 break;
1358 case ::LogicOperation::tag::Equiv:
1359 obj["tag"] = "Equiv";
1360 break;
1361 case ::LogicOperation::tag::Invert:
1362 obj["tag"] = "Invert";
1363 break;
1364 case ::LogicOperation::tag::OrReverse:
1365 obj["tag"] = "OrReverse";
1366 break;
1367 case ::LogicOperation::tag::CopyInverted:
1368 obj["tag"] = "CopyInverted";
1369 break;
1370 case ::LogicOperation::tag::OrInverted:
1371 obj["tag"] = "OrInverted";
1372 break;
1373 case ::LogicOperation::tag::Nand:
1374 obj["tag"] = "Nand";
1375 break;
1376 case ::LogicOperation::tag::Set:
1377 obj["tag"] = "Set";
1378 break;
1379 }
1380 return obj;
1381}
1382
1383template<> std::shared_ptr<LogicOperation> fromJSON<std::shared_ptr<LogicOperation>>(W<std::shared_ptr<LogicOperation>> v, json &obj) {
1384 enum ::LogicOperation::tag tagType;
1385 std::string tag = obj["tag"];
1386 if (tag == "Clear") {
1387 tagType = ::LogicOperation::tag::Clear;
1388 }
1389 else if (tag == "And") {
1390 tagType = ::LogicOperation::tag::And;
1391 }
1392 else if (tag == "AndReverse") {
1393 tagType = ::LogicOperation::tag::AndReverse;
1394 }
1395 else if (tag == "Copy") {
1396 tagType = ::LogicOperation::tag::Copy;
1397 }
1398 else if (tag == "AndInverted") {
1399 tagType = ::LogicOperation::tag::AndInverted;
1400 }
1401 else if (tag == "Noop") {
1402 tagType = ::LogicOperation::tag::Noop;
1403 }
1404 else if (tag == "Xor") {
1405 tagType = ::LogicOperation::tag::Xor;
1406 }
1407 else if (tag == "Or") {
1408 tagType = ::LogicOperation::tag::Or;
1409 }
1410 else if (tag == "Nor") {
1411 tagType = ::LogicOperation::tag::Nor;
1412 }
1413 else if (tag == "Equiv") {
1414 tagType = ::LogicOperation::tag::Equiv;
1415 }
1416 else if (tag == "Invert") {
1417 tagType = ::LogicOperation::tag::Invert;
1418 }
1419 else if (tag == "OrReverse") {
1420 tagType = ::LogicOperation::tag::OrReverse;
1421 }
1422 else if (tag == "CopyInverted") {
1423 tagType = ::LogicOperation::tag::CopyInverted;
1424 }
1425 else if (tag == "OrInverted") {
1426 tagType = ::LogicOperation::tag::OrInverted;
1427 }
1428 else if (tag == "Nand") {
1429 tagType = ::LogicOperation::tag::Nand;
1430 }
1431 else if (tag == "Set") {
1432 tagType = ::LogicOperation::tag::Set;
1433 }
1434 else throw "unknown constructor: " + tag;
1435 std::shared_ptr<::LogicOperation> o(new ::LogicOperation());
1436 o->tag = tagType;
1437 return o;
1438}
1439
1440template<> json toJSON<std::shared_ptr<StencilOps>>(std::shared_ptr<StencilOps> &v) {
1441 json obj({});
1442 switch (v->tag) {
1443 case ::StencilOps::tag::StencilOps:
1444 obj["tag"] = "StencilOps";
1445 {
1446 std::shared_ptr<data::StencilOps> tv = std::static_pointer_cast<data::StencilOps>(v);
1447 obj["frontStencilOp"] = toJSON(tv->frontStencilOp);
1448 obj["backStencilOp"] = toJSON(tv->backStencilOp);
1449 }
1450 break;
1451 }
1452 return obj;
1453}
1454
1455template<> std::shared_ptr<StencilOps> fromJSON<std::shared_ptr<StencilOps>>(W<std::shared_ptr<StencilOps>> v, json &obj) {
1456 enum ::StencilOps::tag tagType;
1457 std::string tag = obj["tag"];
1458 if (tag == "StencilOps") {
1459 tagType = ::StencilOps::tag::StencilOps;
1460 std::shared_ptr<data::StencilOps> tv(new data::StencilOps());
1461 tv->frontStencilOp = fromJSON(W<std::shared_ptr<::StencilOperation>>(), obj["frontStencilOp"]);
1462 tv->backStencilOp = fromJSON(W<std::shared_ptr<::StencilOperation>>(), obj["backStencilOp"]);
1463 return tv;
1464 }
1465 else throw "unknown constructor: " + tag;
1466 std::shared_ptr<::StencilOps> o(new ::StencilOps());
1467 o->tag = tagType;
1468 return o;
1469}
1470
1471template<> json toJSON<std::shared_ptr<StencilTest>>(std::shared_ptr<StencilTest> &v) {
1472 json obj({});
1473 switch (v->tag) {
1474 case ::StencilTest::tag::StencilTest:
1475 obj["tag"] = "StencilTest";
1476 {
1477 std::shared_ptr<data::StencilTest> tv = std::static_pointer_cast<data::StencilTest>(v);
1478 obj["stencilComparision"] = toJSON(tv->stencilComparision);
1479 obj["stencilReference"] = toJSON(tv->stencilReference);
1480 obj["stencilMask"] = toJSON(tv->stencilMask);
1481 }
1482 break;
1483 }
1484 return obj;
1485}
1486
1487template<> std::shared_ptr<StencilTest> fromJSON<std::shared_ptr<StencilTest>>(W<std::shared_ptr<StencilTest>> v, json &obj) {
1488 enum ::StencilTest::tag tagType;
1489 std::string tag = obj["tag"];
1490 if (tag == "StencilTest") {
1491 tagType = ::StencilTest::tag::StencilTest;
1492 std::shared_ptr<data::StencilTest> tv(new data::StencilTest());
1493 tv->stencilComparision = fromJSON(W<std::shared_ptr<::ComparisonFunction>>(), obj["stencilComparision"]);
1494 tv->stencilReference = fromJSON(W<Int32>(), obj["stencilReference"]);
1495 tv->stencilMask = fromJSON(W<Word32>(), obj["stencilMask"]);
1496 return tv;
1497 }
1498 else throw "unknown constructor: " + tag;
1499 std::shared_ptr<::StencilTest> o(new ::StencilTest());
1500 o->tag = tagType;
1501 return o;
1502}
1503
1504template<> json toJSON<std::shared_ptr<StencilTests>>(std::shared_ptr<StencilTests> &v) {
1505 json obj({});
1506 switch (v->tag) {
1507 case ::StencilTests::tag::StencilTests:
1508 obj["tag"] = "StencilTests";
1509 {
1510 std::shared_ptr<data::StencilTests> tv = std::static_pointer_cast<data::StencilTests>(v);
1511 obj["arg0"] = toJSON(tv->_0);
1512 obj["arg1"] = toJSON(tv->_1);
1513 }
1514 break;
1515 }
1516 return obj;
1517}
1518
1519template<> std::shared_ptr<StencilTests> fromJSON<std::shared_ptr<StencilTests>>(W<std::shared_ptr<StencilTests>> v, json &obj) {
1520 enum ::StencilTests::tag tagType;
1521 std::string tag = obj["tag"];
1522 if (tag == "StencilTests") {
1523 tagType = ::StencilTests::tag::StencilTests;
1524 std::shared_ptr<data::StencilTests> tv(new data::StencilTests());
1525 tv->_0 = fromJSON(W<std::shared_ptr<::StencilTest>>(), obj["arg0"]);
1526 tv->_1 = fromJSON(W<std::shared_ptr<::StencilTest>>(), obj["arg1"]);
1527 return tv;
1528 }
1529 else throw "unknown constructor: " + tag;
1530 std::shared_ptr<::StencilTests> o(new ::StencilTests());
1531 o->tag = tagType;
1532 return o;
1533}
1534
1535template<> json toJSON<std::shared_ptr<FetchPrimitive>>(std::shared_ptr<FetchPrimitive> &v) {
1536 json obj({});
1537 switch (v->tag) {
1538 case ::FetchPrimitive::tag::Points:
1539 obj["tag"] = "Points";
1540 break;
1541 case ::FetchPrimitive::tag::Lines:
1542 obj["tag"] = "Lines";
1543 break;
1544 case ::FetchPrimitive::tag::Triangles:
1545 obj["tag"] = "Triangles";
1546 break;
1547 case ::FetchPrimitive::tag::LinesAdjacency:
1548 obj["tag"] = "LinesAdjacency";
1549 break;
1550 case ::FetchPrimitive::tag::TrianglesAdjacency:
1551 obj["tag"] = "TrianglesAdjacency";
1552 break;
1553 }
1554 return obj;
1555}
1556
1557template<> std::shared_ptr<FetchPrimitive> fromJSON<std::shared_ptr<FetchPrimitive>>(W<std::shared_ptr<FetchPrimitive>> v, json &obj) {
1558 enum ::FetchPrimitive::tag tagType;
1559 std::string tag = obj["tag"];
1560 if (tag == "Points") {
1561 tagType = ::FetchPrimitive::tag::Points;
1562 }
1563 else if (tag == "Lines") {
1564 tagType = ::FetchPrimitive::tag::Lines;
1565 }
1566 else if (tag == "Triangles") {
1567 tagType = ::FetchPrimitive::tag::Triangles;
1568 }
1569 else if (tag == "LinesAdjacency") {
1570 tagType = ::FetchPrimitive::tag::LinesAdjacency;
1571 }
1572 else if (tag == "TrianglesAdjacency") {
1573 tagType = ::FetchPrimitive::tag::TrianglesAdjacency;
1574 }
1575 else throw "unknown constructor: " + tag;
1576 std::shared_ptr<::FetchPrimitive> o(new ::FetchPrimitive());
1577 o->tag = tagType;
1578 return o;
1579}
1580
1581template<> json toJSON<std::shared_ptr<OutputPrimitive>>(std::shared_ptr<OutputPrimitive> &v) {
1582 json obj({});
1583 switch (v->tag) {
1584 case ::OutputPrimitive::tag::TrianglesOutput:
1585 obj["tag"] = "TrianglesOutput";
1586 break;
1587 case ::OutputPrimitive::tag::LinesOutput:
1588 obj["tag"] = "LinesOutput";
1589 break;
1590 case ::OutputPrimitive::tag::PointsOutput:
1591 obj["tag"] = "PointsOutput";
1592 break;
1593 }
1594 return obj;
1595}
1596
1597template<> std::shared_ptr<OutputPrimitive> fromJSON<std::shared_ptr<OutputPrimitive>>(W<std::shared_ptr<OutputPrimitive>> v, json &obj) {
1598 enum ::OutputPrimitive::tag tagType;
1599 std::string tag = obj["tag"];
1600 if (tag == "TrianglesOutput") {
1601 tagType = ::OutputPrimitive::tag::TrianglesOutput;
1602 }
1603 else if (tag == "LinesOutput") {
1604 tagType = ::OutputPrimitive::tag::LinesOutput;
1605 }
1606 else if (tag == "PointsOutput") {
1607 tagType = ::OutputPrimitive::tag::PointsOutput;
1608 }
1609 else throw "unknown constructor: " + tag;
1610 std::shared_ptr<::OutputPrimitive> o(new ::OutputPrimitive());
1611 o->tag = tagType;
1612 return o;
1613}
1614
1615template<> json toJSON<std::shared_ptr<ColorArity>>(std::shared_ptr<ColorArity> &v) {
1616 json obj({});
1617 switch (v->tag) {
1618 case ::ColorArity::tag::Red:
1619 obj["tag"] = "Red";
1620 break;
1621 case ::ColorArity::tag::RG:
1622 obj["tag"] = "RG";
1623 break;
1624 case ::ColorArity::tag::RGB:
1625 obj["tag"] = "RGB";
1626 break;
1627 case ::ColorArity::tag::RGBA:
1628 obj["tag"] = "RGBA";
1629 break;
1630 }
1631 return obj;
1632}
1633
1634template<> std::shared_ptr<ColorArity> fromJSON<std::shared_ptr<ColorArity>>(W<std::shared_ptr<ColorArity>> v, json &obj) {
1635 enum ::ColorArity::tag tagType;
1636 std::string tag = obj["tag"];
1637 if (tag == "Red") {
1638 tagType = ::ColorArity::tag::Red;
1639 }
1640 else if (tag == "RG") {
1641 tagType = ::ColorArity::tag::RG;
1642 }
1643 else if (tag == "RGB") {
1644 tagType = ::ColorArity::tag::RGB;
1645 }
1646 else if (tag == "RGBA") {
1647 tagType = ::ColorArity::tag::RGBA;
1648 }
1649 else throw "unknown constructor: " + tag;
1650 std::shared_ptr<::ColorArity> o(new ::ColorArity());
1651 o->tag = tagType;
1652 return o;
1653}
1654
1655template<> json toJSON<std::shared_ptr<Blending>>(std::shared_ptr<Blending> &v) {
1656 json obj({});
1657 switch (v->tag) {
1658 case ::Blending::tag::NoBlending:
1659 obj["tag"] = "NoBlending";
1660 break;
1661 case ::Blending::tag::BlendLogicOp:
1662 obj["tag"] = "BlendLogicOp";
1663 {
1664 std::shared_ptr<data::BlendLogicOp> tv = std::static_pointer_cast<data::BlendLogicOp>(v);
1665 obj["arg0"] = toJSON(tv->_0);
1666 }
1667 break;
1668 case ::Blending::tag::Blend:
1669 obj["tag"] = "Blend";
1670 {
1671 std::shared_ptr<data::Blend> tv = std::static_pointer_cast<data::Blend>(v);
1672 obj["colorEqSrc"] = toJSON(tv->colorEqSrc);
1673 obj["alphaEqSrc"] = toJSON(tv->alphaEqSrc);
1674 obj["colorFSrc"] = toJSON(tv->colorFSrc);
1675 obj["colorFDst"] = toJSON(tv->colorFDst);
1676 obj["alphaFSrc"] = toJSON(tv->alphaFSrc);
1677 obj["alphaFDst"] = toJSON(tv->alphaFDst);
1678 obj["color"] = toJSON(tv->color);
1679 }
1680 break;
1681 }
1682 return obj;
1683}
1684
1685template<> std::shared_ptr<Blending> fromJSON<std::shared_ptr<Blending>>(W<std::shared_ptr<Blending>> v, json &obj) {
1686 enum ::Blending::tag tagType;
1687 std::string tag = obj["tag"];
1688 if (tag == "NoBlending") {
1689 tagType = ::Blending::tag::NoBlending;
1690 }
1691 else if (tag == "BlendLogicOp") {
1692 tagType = ::Blending::tag::BlendLogicOp;
1693 std::shared_ptr<data::BlendLogicOp> tv(new data::BlendLogicOp());
1694 tv->_0 = fromJSON(W<std::shared_ptr<::LogicOperation>>(), obj["arg0"]);
1695 return tv;
1696 }
1697 else if (tag == "Blend") {
1698 tagType = ::Blending::tag::Blend;
1699 std::shared_ptr<data::Blend> tv(new data::Blend());
1700 tv->colorEqSrc = fromJSON(W<std::shared_ptr<::BlendEquation>>(), obj["colorEqSrc"]);
1701 tv->alphaEqSrc = fromJSON(W<std::shared_ptr<::BlendEquation>>(), obj["alphaEqSrc"]);
1702 tv->colorFSrc = fromJSON(W<std::shared_ptr<::BlendingFactor>>(), obj["colorFSrc"]);
1703 tv->colorFDst = fromJSON(W<std::shared_ptr<::BlendingFactor>>(), obj["colorFDst"]);
1704 tv->alphaFSrc = fromJSON(W<std::shared_ptr<::BlendingFactor>>(), obj["alphaFSrc"]);
1705 tv->alphaFDst = fromJSON(W<std::shared_ptr<::BlendingFactor>>(), obj["alphaFDst"]);
1706 tv->color = fromJSON(W<V4F>(), obj["color"]);
1707 return tv;
1708 }
1709 else throw "unknown constructor: " + tag;
1710 std::shared_ptr<::Blending> o(new ::Blending());
1711 o->tag = tagType;
1712 return o;
1713}
1714
1715template<> json toJSON<std::shared_ptr<RasterContext>>(std::shared_ptr<RasterContext> &v) {
1716 json obj({});
1717 switch (v->tag) {
1718 case ::RasterContext::tag::PointCtx:
1719 obj["tag"] = "PointCtx";
1720 {
1721 std::shared_ptr<data::PointCtx> tv = std::static_pointer_cast<data::PointCtx>(v);
1722 obj["arg0"] = toJSON(tv->_0);
1723 obj["arg1"] = toJSON(tv->_1);
1724 obj["arg2"] = toJSON(tv->_2);
1725 }
1726 break;
1727 case ::RasterContext::tag::LineCtx:
1728 obj["tag"] = "LineCtx";
1729 {
1730 std::shared_ptr<data::LineCtx> tv = std::static_pointer_cast<data::LineCtx>(v);
1731 obj["arg0"] = toJSON(tv->_0);
1732 obj["arg1"] = toJSON(tv->_1);
1733 }
1734 break;
1735 case ::RasterContext::tag::TriangleCtx:
1736 obj["tag"] = "TriangleCtx";
1737 {
1738 std::shared_ptr<data::TriangleCtx> tv = std::static_pointer_cast<data::TriangleCtx>(v);
1739 obj["arg0"] = toJSON(tv->_0);
1740 obj["arg1"] = toJSON(tv->_1);
1741 obj["arg2"] = toJSON(tv->_2);
1742 obj["arg3"] = toJSON(tv->_3);
1743 }
1744 break;
1745 }
1746 return obj;
1747}
1748
1749template<> std::shared_ptr<RasterContext> fromJSON<std::shared_ptr<RasterContext>>(W<std::shared_ptr<RasterContext>> v, json &obj) {
1750 enum ::RasterContext::tag tagType;
1751 std::string tag = obj["tag"];
1752 if (tag == "PointCtx") {
1753 tagType = ::RasterContext::tag::PointCtx;
1754 std::shared_ptr<data::PointCtx> tv(new data::PointCtx());
1755 tv->_0 = fromJSON(W<std::shared_ptr<::PointSize>>(), obj["arg0"]);
1756 tv->_1 = fromJSON(W<Float>(), obj["arg1"]);
1757 tv->_2 = fromJSON(W<std::shared_ptr<::PointSpriteCoordOrigin>>(), obj["arg2"]);
1758 return tv;
1759 }
1760 else if (tag == "LineCtx") {
1761 tagType = ::RasterContext::tag::LineCtx;
1762 std::shared_ptr<data::LineCtx> tv(new data::LineCtx());
1763 tv->_0 = fromJSON(W<Float>(), obj["arg0"]);
1764 tv->_1 = fromJSON(W<std::shared_ptr<::ProvokingVertex>>(), obj["arg1"]);
1765 return tv;
1766 }
1767 else if (tag == "TriangleCtx") {
1768 tagType = ::RasterContext::tag::TriangleCtx;
1769 std::shared_ptr<data::TriangleCtx> tv(new data::TriangleCtx());
1770 tv->_0 = fromJSON(W<std::shared_ptr<::CullMode>>(), obj["arg0"]);
1771 tv->_1 = fromJSON(W<std::shared_ptr<::PolygonMode>>(), obj["arg1"]);
1772 tv->_2 = fromJSON(W<std::shared_ptr<::PolygonOffset>>(), obj["arg2"]);
1773 tv->_3 = fromJSON(W<std::shared_ptr<::ProvokingVertex>>(), obj["arg3"]);
1774 return tv;
1775 }
1776 else throw "unknown constructor: " + tag;
1777 std::shared_ptr<::RasterContext> o(new ::RasterContext());
1778 o->tag = tagType;
1779 return o;
1780}
1781
1782template<> json toJSON<std::shared_ptr<FragmentOperation>>(std::shared_ptr<FragmentOperation> &v) {
1783 json obj({});
1784 switch (v->tag) {
1785 case ::FragmentOperation::tag::DepthOp:
1786 obj["tag"] = "DepthOp";
1787 {
1788 std::shared_ptr<data::DepthOp> tv = std::static_pointer_cast<data::DepthOp>(v);
1789 obj["arg0"] = toJSON(tv->_0);
1790 obj["arg1"] = toJSON(tv->_1);
1791 }
1792 break;
1793 case ::FragmentOperation::tag::StencilOp:
1794 obj["tag"] = "StencilOp";
1795 {
1796 std::shared_ptr<data::StencilOp> tv = std::static_pointer_cast<data::StencilOp>(v);
1797 obj["arg0"] = toJSON(tv->_0);
1798 obj["arg1"] = toJSON(tv->_1);
1799 obj["arg2"] = toJSON(tv->_2);
1800 }
1801 break;
1802 case ::FragmentOperation::tag::ColorOp:
1803 obj["tag"] = "ColorOp";
1804 {
1805 std::shared_ptr<data::ColorOp> tv = std::static_pointer_cast<data::ColorOp>(v);
1806 obj["arg0"] = toJSON(tv->_0);
1807 obj["arg1"] = toJSON(tv->_1);
1808 }
1809 break;
1810 }
1811 return obj;
1812}
1813
1814template<> std::shared_ptr<FragmentOperation> fromJSON<std::shared_ptr<FragmentOperation>>(W<std::shared_ptr<FragmentOperation>> v, json &obj) {
1815 enum ::FragmentOperation::tag tagType;
1816 std::string tag = obj["tag"];
1817 if (tag == "DepthOp") {
1818 tagType = ::FragmentOperation::tag::DepthOp;
1819 std::shared_ptr<data::DepthOp> tv(new data::DepthOp());
1820 tv->_0 = fromJSON(W<std::shared_ptr<::DepthFunction>>(), obj["arg0"]);
1821 tv->_1 = fromJSON(W<Bool>(), obj["arg1"]);
1822 return tv;
1823 }
1824 else if (tag == "StencilOp") {
1825 tagType = ::FragmentOperation::tag::StencilOp;
1826 std::shared_ptr<data::StencilOp> tv(new data::StencilOp());
1827 tv->_0 = fromJSON(W<std::shared_ptr<::StencilTests>>(), obj["arg0"]);
1828 tv->_1 = fromJSON(W<std::shared_ptr<::StencilOps>>(), obj["arg1"]);
1829 tv->_2 = fromJSON(W<std::shared_ptr<::StencilOps>>(), obj["arg2"]);
1830 return tv;
1831 }
1832 else if (tag == "ColorOp") {
1833 tagType = ::FragmentOperation::tag::ColorOp;
1834 std::shared_ptr<data::ColorOp> tv(new data::ColorOp());
1835 tv->_0 = fromJSON(W<std::shared_ptr<::Blending>>(), obj["arg0"]);
1836 tv->_1 = fromJSON(W<std::shared_ptr<::Value>>(), obj["arg1"]);
1837 return tv;
1838 }
1839 else throw "unknown constructor: " + tag;
1840 std::shared_ptr<::FragmentOperation> o(new ::FragmentOperation());
1841 o->tag = tagType;
1842 return o;
1843}
1844
1845template<> json toJSON<std::shared_ptr<AccumulationContext>>(std::shared_ptr<AccumulationContext> &v) {
1846 json obj({});
1847 switch (v->tag) {
1848 case ::AccumulationContext::tag::AccumulationContext:
1849 obj["tag"] = "AccumulationContext";
1850 {
1851 std::shared_ptr<data::AccumulationContext> tv = std::static_pointer_cast<data::AccumulationContext>(v);
1852 obj["accViewportName"] = toJSON(tv->accViewportName);
1853 obj["accOperations"] = toJSON(tv->accOperations);
1854 }
1855 break;
1856 }
1857 return obj;
1858}
1859
1860template<> std::shared_ptr<AccumulationContext> fromJSON<std::shared_ptr<AccumulationContext>>(W<std::shared_ptr<AccumulationContext>> v, json &obj) {
1861 enum ::AccumulationContext::tag tagType;
1862 std::string tag = obj["tag"];
1863 if (tag == "AccumulationContext") {
1864 tagType = ::AccumulationContext::tag::AccumulationContext;
1865 std::shared_ptr<data::AccumulationContext> tv(new data::AccumulationContext());
1866 tv->accViewportName = fromJSON(W<Maybe<String>>(), obj["accViewportName"]);
1867 tv->accOperations = fromJSON(W<std::vector<std::shared_ptr<::FragmentOperation>>>(), obj["accOperations"]);
1868 return tv;
1869 }
1870 else throw "unknown constructor: " + tag;
1871 std::shared_ptr<::AccumulationContext> o(new ::AccumulationContext());
1872 o->tag = tagType;
1873 return o;
1874}
1875
1876template<> json toJSON<std::shared_ptr<TextureDataType>>(std::shared_ptr<TextureDataType> &v) {
1877 json obj({});
1878 switch (v->tag) {
1879 case ::TextureDataType::tag::FloatT:
1880 obj["tag"] = "FloatT";
1881 {
1882 std::shared_ptr<data::FloatT> tv = std::static_pointer_cast<data::FloatT>(v);
1883 obj["arg0"] = toJSON(tv->_0);
1884 }
1885 break;
1886 case ::TextureDataType::tag::IntT:
1887 obj["tag"] = "IntT";
1888 {
1889 std::shared_ptr<data::IntT> tv = std::static_pointer_cast<data::IntT>(v);
1890 obj["arg0"] = toJSON(tv->_0);
1891 }
1892 break;
1893 case ::TextureDataType::tag::WordT:
1894 obj["tag"] = "WordT";
1895 {
1896 std::shared_ptr<data::WordT> tv = std::static_pointer_cast<data::WordT>(v);
1897 obj["arg0"] = toJSON(tv->_0);
1898 }
1899 break;
1900 case ::TextureDataType::tag::ShadowT:
1901 obj["tag"] = "ShadowT";
1902 break;
1903 }
1904 return obj;
1905}
1906
1907template<> std::shared_ptr<TextureDataType> fromJSON<std::shared_ptr<TextureDataType>>(W<std::shared_ptr<TextureDataType>> v, json &obj) {
1908 enum ::TextureDataType::tag tagType;
1909 std::string tag = obj["tag"];
1910 if (tag == "FloatT") {
1911 tagType = ::TextureDataType::tag::FloatT;
1912 std::shared_ptr<data::FloatT> tv(new data::FloatT());
1913 tv->_0 = fromJSON(W<std::shared_ptr<::ColorArity>>(), obj["arg0"]);
1914 return tv;
1915 }
1916 else if (tag == "IntT") {
1917 tagType = ::TextureDataType::tag::IntT;
1918 std::shared_ptr<data::IntT> tv(new data::IntT());
1919 tv->_0 = fromJSON(W<std::shared_ptr<::ColorArity>>(), obj["arg0"]);
1920 return tv;
1921 }
1922 else if (tag == "WordT") {
1923 tagType = ::TextureDataType::tag::WordT;
1924 std::shared_ptr<data::WordT> tv(new data::WordT());
1925 tv->_0 = fromJSON(W<std::shared_ptr<::ColorArity>>(), obj["arg0"]);
1926 return tv;
1927 }
1928 else if (tag == "ShadowT") {
1929 tagType = ::TextureDataType::tag::ShadowT;
1930 }
1931 else throw "unknown constructor: " + tag;
1932 std::shared_ptr<::TextureDataType> o(new ::TextureDataType());
1933 o->tag = tagType;
1934 return o;
1935}
1936
1937template<> json toJSON<std::shared_ptr<TextureType>>(std::shared_ptr<TextureType> &v) {
1938 json obj({});
1939 switch (v->tag) {
1940 case ::TextureType::tag::Texture1D:
1941 obj["tag"] = "Texture1D";
1942 {
1943 std::shared_ptr<data::Texture1D> tv = std::static_pointer_cast<data::Texture1D>(v);
1944 obj["arg0"] = toJSON(tv->_0);
1945 obj["arg1"] = toJSON(tv->_1);
1946 }
1947 break;
1948 case ::TextureType::tag::Texture2D:
1949 obj["tag"] = "Texture2D";
1950 {
1951 std::shared_ptr<data::Texture2D> tv = std::static_pointer_cast<data::Texture2D>(v);
1952 obj["arg0"] = toJSON(tv->_0);
1953 obj["arg1"] = toJSON(tv->_1);
1954 }
1955 break;
1956 case ::TextureType::tag::Texture3D:
1957 obj["tag"] = "Texture3D";
1958 {
1959 std::shared_ptr<data::Texture3D> tv = std::static_pointer_cast<data::Texture3D>(v);
1960 obj["arg0"] = toJSON(tv->_0);
1961 }
1962 break;
1963 case ::TextureType::tag::TextureCube:
1964 obj["tag"] = "TextureCube";
1965 {
1966 std::shared_ptr<data::TextureCube> tv = std::static_pointer_cast<data::TextureCube>(v);
1967 obj["arg0"] = toJSON(tv->_0);
1968 }
1969 break;
1970 case ::TextureType::tag::TextureRect:
1971 obj["tag"] = "TextureRect";
1972 {
1973 std::shared_ptr<data::TextureRect> tv = std::static_pointer_cast<data::TextureRect>(v);
1974 obj["arg0"] = toJSON(tv->_0);
1975 }
1976 break;
1977 case ::TextureType::tag::Texture2DMS:
1978 obj["tag"] = "Texture2DMS";
1979 {
1980 std::shared_ptr<data::Texture2DMS> tv = std::static_pointer_cast<data::Texture2DMS>(v);
1981 obj["arg0"] = toJSON(tv->_0);
1982 obj["arg1"] = toJSON(tv->_1);
1983 obj["arg2"] = toJSON(tv->_2);
1984 obj["arg3"] = toJSON(tv->_3);
1985 }
1986 break;
1987 case ::TextureType::tag::TextureBuffer:
1988 obj["tag"] = "TextureBuffer";
1989 {
1990 std::shared_ptr<data::TextureBuffer> tv = std::static_pointer_cast<data::TextureBuffer>(v);
1991 obj["arg0"] = toJSON(tv->_0);
1992 }
1993 break;
1994 }
1995 return obj;
1996}
1997
1998template<> std::shared_ptr<TextureType> fromJSON<std::shared_ptr<TextureType>>(W<std::shared_ptr<TextureType>> v, json &obj) {
1999 enum ::TextureType::tag tagType;
2000 std::string tag = obj["tag"];
2001 if (tag == "Texture1D") {
2002 tagType = ::TextureType::tag::Texture1D;
2003 std::shared_ptr<data::Texture1D> tv(new data::Texture1D());
2004 tv->_0 = fromJSON(W<std::shared_ptr<::TextureDataType>>(), obj["arg0"]);
2005 tv->_1 = fromJSON(W<Int>(), obj["arg1"]);
2006 return tv;
2007 }
2008 else if (tag == "Texture2D") {
2009 tagType = ::TextureType::tag::Texture2D;
2010 std::shared_ptr<data::Texture2D> tv(new data::Texture2D());
2011 tv->_0 = fromJSON(W<std::shared_ptr<::TextureDataType>>(), obj["arg0"]);
2012 tv->_1 = fromJSON(W<Int>(), obj["arg1"]);
2013 return tv;
2014 }
2015 else if (tag == "Texture3D") {
2016 tagType = ::TextureType::tag::Texture3D;
2017 std::shared_ptr<data::Texture3D> tv(new data::Texture3D());
2018 tv->_0 = fromJSON(W<std::shared_ptr<::TextureDataType>>(), obj["arg0"]);
2019 return tv;
2020 }
2021 else if (tag == "TextureCube") {
2022 tagType = ::TextureType::tag::TextureCube;
2023 std::shared_ptr<data::TextureCube> tv(new data::TextureCube());
2024 tv->_0 = fromJSON(W<std::shared_ptr<::TextureDataType>>(), obj["arg0"]);
2025 return tv;
2026 }
2027 else if (tag == "TextureRect") {
2028 tagType = ::TextureType::tag::TextureRect;
2029 std::shared_ptr<data::TextureRect> tv(new data::TextureRect());
2030 tv->_0 = fromJSON(W<std::shared_ptr<::TextureDataType>>(), obj["arg0"]);
2031 return tv;
2032 }
2033 else if (tag == "Texture2DMS") {
2034 tagType = ::TextureType::tag::Texture2DMS;
2035 std::shared_ptr<data::Texture2DMS> tv(new data::Texture2DMS());
2036 tv->_0 = fromJSON(W<std::shared_ptr<::TextureDataType>>(), obj["arg0"]);
2037 tv->_1 = fromJSON(W<Int>(), obj["arg1"]);
2038 tv->_2 = fromJSON(W<Int>(), obj["arg2"]);
2039 tv->_3 = fromJSON(W<Bool>(), obj["arg3"]);
2040 return tv;
2041 }
2042 else if (tag == "TextureBuffer") {
2043 tagType = ::TextureType::tag::TextureBuffer;
2044 std::shared_ptr<data::TextureBuffer> tv(new data::TextureBuffer());
2045 tv->_0 = fromJSON(W<std::shared_ptr<::TextureDataType>>(), obj["arg0"]);
2046 return tv;
2047 }
2048 else throw "unknown constructor: " + tag;
2049 std::shared_ptr<::TextureType> o(new ::TextureType());
2050 o->tag = tagType;
2051 return o;
2052}
2053
2054template<> json toJSON<std::shared_ptr<MipMap>>(std::shared_ptr<MipMap> &v) {
2055 json obj({});
2056 switch (v->tag) {
2057 case ::MipMap::tag::Mip:
2058 obj["tag"] = "Mip";
2059 {
2060 std::shared_ptr<data::Mip> tv = std::static_pointer_cast<data::Mip>(v);
2061 obj["arg0"] = toJSON(tv->_0);
2062 obj["arg1"] = toJSON(tv->_1);
2063 }
2064 break;
2065 case ::MipMap::tag::NoMip:
2066 obj["tag"] = "NoMip";
2067 break;
2068 case ::MipMap::tag::AutoMip:
2069 obj["tag"] = "AutoMip";
2070 {
2071 std::shared_ptr<data::AutoMip> tv = std::static_pointer_cast<data::AutoMip>(v);
2072 obj["arg0"] = toJSON(tv->_0);
2073 obj["arg1"] = toJSON(tv->_1);
2074 }
2075 break;
2076 }
2077 return obj;
2078}
2079
2080template<> std::shared_ptr<MipMap> fromJSON<std::shared_ptr<MipMap>>(W<std::shared_ptr<MipMap>> v, json &obj) {
2081 enum ::MipMap::tag tagType;
2082 std::string tag = obj["tag"];
2083 if (tag == "Mip") {
2084 tagType = ::MipMap::tag::Mip;
2085 std::shared_ptr<data::Mip> tv(new data::Mip());
2086 tv->_0 = fromJSON(W<Int>(), obj["arg0"]);
2087 tv->_1 = fromJSON(W<Int>(), obj["arg1"]);
2088 return tv;
2089 }
2090 else if (tag == "NoMip") {
2091 tagType = ::MipMap::tag::NoMip;
2092 }
2093 else if (tag == "AutoMip") {
2094 tagType = ::MipMap::tag::AutoMip;
2095 std::shared_ptr<data::AutoMip> tv(new data::AutoMip());
2096 tv->_0 = fromJSON(W<Int>(), obj["arg0"]);
2097 tv->_1 = fromJSON(W<Int>(), obj["arg1"]);
2098 return tv;
2099 }
2100 else throw "unknown constructor: " + tag;
2101 std::shared_ptr<::MipMap> o(new ::MipMap());
2102 o->tag = tagType;
2103 return o;
2104}
2105
2106template<> json toJSON<std::shared_ptr<Filter>>(std::shared_ptr<Filter> &v) {
2107 json obj({});
2108 switch (v->tag) {
2109 case ::Filter::tag::Nearest:
2110 obj["tag"] = "Nearest";
2111 break;
2112 case ::Filter::tag::Linear:
2113 obj["tag"] = "Linear";
2114 break;
2115 case ::Filter::tag::NearestMipmapNearest:
2116 obj["tag"] = "NearestMipmapNearest";
2117 break;
2118 case ::Filter::tag::NearestMipmapLinear:
2119 obj["tag"] = "NearestMipmapLinear";
2120 break;
2121 case ::Filter::tag::LinearMipmapNearest:
2122 obj["tag"] = "LinearMipmapNearest";
2123 break;
2124 case ::Filter::tag::LinearMipmapLinear:
2125 obj["tag"] = "LinearMipmapLinear";
2126 break;
2127 }
2128 return obj;
2129}
2130
2131template<> std::shared_ptr<Filter> fromJSON<std::shared_ptr<Filter>>(W<std::shared_ptr<Filter>> v, json &obj) {
2132 enum ::Filter::tag tagType;
2133 std::string tag = obj["tag"];
2134 if (tag == "Nearest") {
2135 tagType = ::Filter::tag::Nearest;
2136 }
2137 else if (tag == "Linear") {
2138 tagType = ::Filter::tag::Linear;
2139 }
2140 else if (tag == "NearestMipmapNearest") {
2141 tagType = ::Filter::tag::NearestMipmapNearest;
2142 }
2143 else if (tag == "NearestMipmapLinear") {
2144 tagType = ::Filter::tag::NearestMipmapLinear;
2145 }
2146 else if (tag == "LinearMipmapNearest") {
2147 tagType = ::Filter::tag::LinearMipmapNearest;
2148 }
2149 else if (tag == "LinearMipmapLinear") {
2150 tagType = ::Filter::tag::LinearMipmapLinear;
2151 }
2152 else throw "unknown constructor: " + tag;
2153 std::shared_ptr<::Filter> o(new ::Filter());
2154 o->tag = tagType;
2155 return o;
2156}
2157
2158template<> json toJSON<std::shared_ptr<EdgeMode>>(std::shared_ptr<EdgeMode> &v) {
2159 json obj({});
2160 switch (v->tag) {
2161 case ::EdgeMode::tag::Repeat:
2162 obj["tag"] = "Repeat";
2163 break;
2164 case ::EdgeMode::tag::MirroredRepeat:
2165 obj["tag"] = "MirroredRepeat";
2166 break;
2167 case ::EdgeMode::tag::ClampToEdge:
2168 obj["tag"] = "ClampToEdge";
2169 break;
2170 case ::EdgeMode::tag::ClampToBorder:
2171 obj["tag"] = "ClampToBorder";
2172 break;
2173 }
2174 return obj;
2175}
2176
2177template<> std::shared_ptr<EdgeMode> fromJSON<std::shared_ptr<EdgeMode>>(W<std::shared_ptr<EdgeMode>> v, json &obj) {
2178 enum ::EdgeMode::tag tagType;
2179 std::string tag = obj["tag"];
2180 if (tag == "Repeat") {
2181 tagType = ::EdgeMode::tag::Repeat;
2182 }
2183 else if (tag == "MirroredRepeat") {
2184 tagType = ::EdgeMode::tag::MirroredRepeat;
2185 }
2186 else if (tag == "ClampToEdge") {
2187 tagType = ::EdgeMode::tag::ClampToEdge;
2188 }
2189 else if (tag == "ClampToBorder") {
2190 tagType = ::EdgeMode::tag::ClampToBorder;
2191 }
2192 else throw "unknown constructor: " + tag;
2193 std::shared_ptr<::EdgeMode> o(new ::EdgeMode());
2194 o->tag = tagType;
2195 return o;
2196}
2197
2198template<> json toJSON<std::shared_ptr<ImageSemantic>>(std::shared_ptr<ImageSemantic> &v) {
2199 json obj({});
2200 switch (v->tag) {
2201 case ::ImageSemantic::tag::Depth:
2202 obj["tag"] = "Depth";
2203 break;
2204 case ::ImageSemantic::tag::Stencil:
2205 obj["tag"] = "Stencil";
2206 break;
2207 case ::ImageSemantic::tag::Color:
2208 obj["tag"] = "Color";
2209 break;
2210 }
2211 return obj;
2212}
2213
2214template<> std::shared_ptr<ImageSemantic> fromJSON<std::shared_ptr<ImageSemantic>>(W<std::shared_ptr<ImageSemantic>> v, json &obj) {
2215 enum ::ImageSemantic::tag tagType;
2216 std::string tag = obj["tag"];
2217 if (tag == "Depth") {
2218 tagType = ::ImageSemantic::tag::Depth;
2219 }
2220 else if (tag == "Stencil") {
2221 tagType = ::ImageSemantic::tag::Stencil;
2222 }
2223 else if (tag == "Color") {
2224 tagType = ::ImageSemantic::tag::Color;
2225 }
2226 else throw "unknown constructor: " + tag;
2227 std::shared_ptr<::ImageSemantic> o(new ::ImageSemantic());
2228 o->tag = tagType;
2229 return o;
2230}
2231
2232template<> json toJSON<std::shared_ptr<ImageRef>>(std::shared_ptr<ImageRef> &v) {
2233 json obj({});
2234 switch (v->tag) {
2235 case ::ImageRef::tag::TextureImage:
2236 obj["tag"] = "TextureImage";
2237 {
2238 std::shared_ptr<data::TextureImage> tv = std::static_pointer_cast<data::TextureImage>(v);
2239 obj["arg0"] = toJSON(tv->_0);
2240 obj["arg1"] = toJSON(tv->_1);
2241 obj["arg2"] = toJSON(tv->_2);
2242 }
2243 break;
2244 case ::ImageRef::tag::Framebuffer:
2245 obj["tag"] = "Framebuffer";
2246 {
2247 std::shared_ptr<data::Framebuffer> tv = std::static_pointer_cast<data::Framebuffer>(v);
2248 obj["arg0"] = toJSON(tv->_0);
2249 }
2250 break;
2251 }
2252 return obj;
2253}
2254
2255template<> std::shared_ptr<ImageRef> fromJSON<std::shared_ptr<ImageRef>>(W<std::shared_ptr<ImageRef>> v, json &obj) {
2256 enum ::ImageRef::tag tagType;
2257 std::string tag = obj["tag"];
2258 if (tag == "TextureImage") {
2259 tagType = ::ImageRef::tag::TextureImage;
2260 std::shared_ptr<data::TextureImage> tv(new data::TextureImage());
2261 tv->_0 = fromJSON(W<::TextureName>(), obj["arg0"]);
2262 tv->_1 = fromJSON(W<Int>(), obj["arg1"]);
2263 tv->_2 = fromJSON(W<Maybe<Int>>(), obj["arg2"]);
2264 return tv;
2265 }
2266 else if (tag == "Framebuffer") {
2267 tagType = ::ImageRef::tag::Framebuffer;
2268 std::shared_ptr<data::Framebuffer> tv(new data::Framebuffer());
2269 tv->_0 = fromJSON(W<std::shared_ptr<::ImageSemantic>>(), obj["arg0"]);
2270 return tv;
2271 }
2272 else throw "unknown constructor: " + tag;
2273 std::shared_ptr<::ImageRef> o(new ::ImageRef());
2274 o->tag = tagType;
2275 return o;
2276}
2277
2278template<> json toJSON<std::shared_ptr<ClearImage>>(std::shared_ptr<ClearImage> &v) {
2279 json obj({});
2280 switch (v->tag) {
2281 case ::ClearImage::tag::ClearImage:
2282 obj["tag"] = "ClearImage";
2283 {
2284 std::shared_ptr<data::ClearImage> tv = std::static_pointer_cast<data::ClearImage>(v);
2285 obj["imageSemantic"] = toJSON(tv->imageSemantic);
2286 obj["clearValue"] = toJSON(tv->clearValue);
2287 }
2288 break;
2289 }
2290 return obj;
2291}
2292
2293template<> std::shared_ptr<ClearImage> fromJSON<std::shared_ptr<ClearImage>>(W<std::shared_ptr<ClearImage>> v, json &obj) {
2294 enum ::ClearImage::tag tagType;
2295 std::string tag = obj["tag"];
2296 if (tag == "ClearImage") {
2297 tagType = ::ClearImage::tag::ClearImage;
2298 std::shared_ptr<data::ClearImage> tv(new data::ClearImage());
2299 tv->imageSemantic = fromJSON(W<std::shared_ptr<::ImageSemantic>>(), obj["imageSemantic"]);
2300 tv->clearValue = fromJSON(W<std::shared_ptr<::Value>>(), obj["clearValue"]);
2301 return tv;
2302 }
2303 else throw "unknown constructor: " + tag;
2304 std::shared_ptr<::ClearImage> o(new ::ClearImage());
2305 o->tag = tagType;
2306 return o;
2307}
2308
2309template<> json toJSON<std::shared_ptr<Command>>(std::shared_ptr<Command> &v) {
2310 json obj({});
2311 switch (v->tag) {
2312 case ::Command::tag::SetRasterContext:
2313 obj["tag"] = "SetRasterContext";
2314 {
2315 std::shared_ptr<data::SetRasterContext> tv = std::static_pointer_cast<data::SetRasterContext>(v);
2316 obj["arg0"] = toJSON(tv->_0);
2317 }
2318 break;
2319 case ::Command::tag::SetAccumulationContext:
2320 obj["tag"] = "SetAccumulationContext";
2321 {
2322 std::shared_ptr<data::SetAccumulationContext> tv = std::static_pointer_cast<data::SetAccumulationContext>(v);
2323 obj["arg0"] = toJSON(tv->_0);
2324 }
2325 break;
2326 case ::Command::tag::SetRenderTarget:
2327 obj["tag"] = "SetRenderTarget";
2328 {
2329 std::shared_ptr<data::SetRenderTarget> tv = std::static_pointer_cast<data::SetRenderTarget>(v);
2330 obj["arg0"] = toJSON(tv->_0);
2331 }
2332 break;
2333 case ::Command::tag::SetProgram:
2334 obj["tag"] = "SetProgram";
2335 {
2336 std::shared_ptr<data::SetProgram> tv = std::static_pointer_cast<data::SetProgram>(v);
2337 obj["arg0"] = toJSON(tv->_0);
2338 }
2339 break;
2340 case ::Command::tag::SetSamplerUniform:
2341 obj["tag"] = "SetSamplerUniform";
2342 {
2343 std::shared_ptr<data::SetSamplerUniform> tv = std::static_pointer_cast<data::SetSamplerUniform>(v);
2344 obj["arg0"] = toJSON(tv->_0);
2345 obj["arg1"] = toJSON(tv->_1);
2346 }
2347 break;
2348 case ::Command::tag::SetTexture:
2349 obj["tag"] = "SetTexture";
2350 {
2351 std::shared_ptr<data::SetTexture> tv = std::static_pointer_cast<data::SetTexture>(v);
2352 obj["arg0"] = toJSON(tv->_0);
2353 obj["arg1"] = toJSON(tv->_1);
2354 }
2355 break;
2356 case ::Command::tag::SetSampler:
2357 obj["tag"] = "SetSampler";
2358 {
2359 std::shared_ptr<data::SetSampler> tv = std::static_pointer_cast<data::SetSampler>(v);
2360 obj["arg0"] = toJSON(tv->_0);
2361 obj["arg1"] = toJSON(tv->_1);
2362 }
2363 break;
2364 case ::Command::tag::RenderSlot:
2365 obj["tag"] = "RenderSlot";
2366 {
2367 std::shared_ptr<data::RenderSlot> tv = std::static_pointer_cast<data::RenderSlot>(v);
2368 obj["arg0"] = toJSON(tv->_0);
2369 }
2370 break;
2371 case ::Command::tag::RenderStream:
2372 obj["tag"] = "RenderStream";
2373 {
2374 std::shared_ptr<data::RenderStream> tv = std::static_pointer_cast<data::RenderStream>(v);
2375 obj["arg0"] = toJSON(tv->_0);
2376 }
2377 break;
2378 case ::Command::tag::ClearRenderTarget:
2379 obj["tag"] = "ClearRenderTarget";
2380 {
2381 std::shared_ptr<data::ClearRenderTarget> tv = std::static_pointer_cast<data::ClearRenderTarget>(v);
2382 obj["arg0"] = toJSON(tv->_0);
2383 }
2384 break;
2385 case ::Command::tag::GenerateMipMap:
2386 obj["tag"] = "GenerateMipMap";
2387 {
2388 std::shared_ptr<data::GenerateMipMap> tv = std::static_pointer_cast<data::GenerateMipMap>(v);
2389 obj["arg0"] = toJSON(tv->_0);
2390 }
2391 break;
2392 case ::Command::tag::SaveImage:
2393 obj["tag"] = "SaveImage";
2394 {
2395 std::shared_ptr<data::SaveImage> tv = std::static_pointer_cast<data::SaveImage>(v);
2396 obj["arg0"] = toJSON(tv->_0);
2397 obj["arg1"] = toJSON(tv->_1);
2398 }
2399 break;
2400 case ::Command::tag::LoadImage:
2401 obj["tag"] = "LoadImage";
2402 {
2403 std::shared_ptr<data::LoadImage> tv = std::static_pointer_cast<data::LoadImage>(v);
2404 obj["arg0"] = toJSON(tv->_0);
2405 obj["arg1"] = toJSON(tv->_1);
2406 }
2407 break;
2408 }
2409 return obj;
2410}
2411
2412template<> std::shared_ptr<Command> fromJSON<std::shared_ptr<Command>>(W<std::shared_ptr<Command>> v, json &obj) {
2413 enum ::Command::tag tagType;
2414 std::string tag = obj["tag"];
2415 if (tag == "SetRasterContext") {
2416 tagType = ::Command::tag::SetRasterContext;
2417 std::shared_ptr<data::SetRasterContext> tv(new data::SetRasterContext());
2418 tv->_0 = fromJSON(W<std::shared_ptr<::RasterContext>>(), obj["arg0"]);
2419 return tv;
2420 }
2421 else if (tag == "SetAccumulationContext") {
2422 tagType = ::Command::tag::SetAccumulationContext;
2423 std::shared_ptr<data::SetAccumulationContext> tv(new data::SetAccumulationContext());
2424 tv->_0 = fromJSON(W<std::shared_ptr<::AccumulationContext>>(), obj["arg0"]);
2425 return tv;
2426 }
2427 else if (tag == "SetRenderTarget") {
2428 tagType = ::Command::tag::SetRenderTarget;
2429 std::shared_ptr<data::SetRenderTarget> tv(new data::SetRenderTarget());
2430 tv->_0 = fromJSON(W<::RenderTargetName>(), obj["arg0"]);
2431 return tv;
2432 }
2433 else if (tag == "SetProgram") {
2434 tagType = ::Command::tag::SetProgram;
2435 std::shared_ptr<data::SetProgram> tv(new data::SetProgram());
2436 tv->_0 = fromJSON(W<::ProgramName>(), obj["arg0"]);
2437 return tv;
2438 }
2439 else if (tag == "SetSamplerUniform") {
2440 tagType = ::Command::tag::SetSamplerUniform;
2441 std::shared_ptr<data::SetSamplerUniform> tv(new data::SetSamplerUniform());
2442 tv->_0 = fromJSON(W<::UniformName>(), obj["arg0"]);
2443 tv->_1 = fromJSON(W<::TextureUnit>(), obj["arg1"]);
2444 return tv;
2445 }
2446 else if (tag == "SetTexture") {
2447 tagType = ::Command::tag::SetTexture;
2448 std::shared_ptr<data::SetTexture> tv(new data::SetTexture());
2449 tv->_0 = fromJSON(W<::TextureUnit>(), obj["arg0"]);
2450 tv->_1 = fromJSON(W<::TextureName>(), obj["arg1"]);
2451 return tv;
2452 }
2453 else if (tag == "SetSampler") {
2454 tagType = ::Command::tag::SetSampler;
2455 std::shared_ptr<data::SetSampler> tv(new data::SetSampler());
2456 tv->_0 = fromJSON(W<::TextureUnit>(), obj["arg0"]);
2457 tv->_1 = fromJSON(W<Maybe<::SamplerName>>(), obj["arg1"]);
2458 return tv;
2459 }
2460 else if (tag == "RenderSlot") {
2461 tagType = ::Command::tag::RenderSlot;
2462 std::shared_ptr<data::RenderSlot> tv(new data::RenderSlot());
2463 tv->_0 = fromJSON(W<::SlotName>(), obj["arg0"]);
2464 return tv;
2465 }
2466 else if (tag == "RenderStream") {
2467 tagType = ::Command::tag::RenderStream;
2468 std::shared_ptr<data::RenderStream> tv(new data::RenderStream());
2469 tv->_0 = fromJSON(W<::StreamName>(), obj["arg0"]);
2470 return tv;
2471 }
2472 else if (tag == "ClearRenderTarget") {
2473 tagType = ::Command::tag::ClearRenderTarget;
2474 std::shared_ptr<data::ClearRenderTarget> tv(new data::ClearRenderTarget());
2475 tv->_0 = fromJSON(W<std::vector<std::shared_ptr<::ClearImage>>>(), obj["arg0"]);
2476 return tv;
2477 }
2478 else if (tag == "GenerateMipMap") {
2479 tagType = ::Command::tag::GenerateMipMap;
2480 std::shared_ptr<data::GenerateMipMap> tv(new data::GenerateMipMap());
2481 tv->_0 = fromJSON(W<::TextureUnit>(), obj["arg0"]);
2482 return tv;
2483 }
2484 else if (tag == "SaveImage") {
2485 tagType = ::Command::tag::SaveImage;
2486 std::shared_ptr<data::SaveImage> tv(new data::SaveImage());
2487 tv->_0 = fromJSON(W<::FrameBufferComponent>(), obj["arg0"]);
2488 tv->_1 = fromJSON(W<std::shared_ptr<::ImageRef>>(), obj["arg1"]);
2489 return tv;
2490 }
2491 else if (tag == "LoadImage") {
2492 tagType = ::Command::tag::LoadImage;
2493 std::shared_ptr<data::LoadImage> tv(new data::LoadImage());
2494 tv->_0 = fromJSON(W<std::shared_ptr<::ImageRef>>(), obj["arg0"]);
2495 tv->_1 = fromJSON(W<::FrameBufferComponent>(), obj["arg1"]);
2496 return tv;
2497 }
2498 else throw "unknown constructor: " + tag;
2499 std::shared_ptr<::Command> o(new ::Command());
2500 o->tag = tagType;
2501 return o;
2502}
2503
2504template<> json toJSON<std::shared_ptr<SamplerDescriptor>>(std::shared_ptr<SamplerDescriptor> &v) {
2505 json obj({});
2506 switch (v->tag) {
2507 case ::SamplerDescriptor::tag::SamplerDescriptor:
2508 obj["tag"] = "SamplerDescriptor";
2509 {
2510 std::shared_ptr<data::SamplerDescriptor> tv = std::static_pointer_cast<data::SamplerDescriptor>(v);
2511 obj["samplerWrapS"] = toJSON(tv->samplerWrapS);
2512 obj["samplerWrapT"] = toJSON(tv->samplerWrapT);
2513 obj["samplerWrapR"] = toJSON(tv->samplerWrapR);
2514 obj["samplerMinFilter"] = toJSON(tv->samplerMinFilter);
2515 obj["samplerMagFilter"] = toJSON(tv->samplerMagFilter);
2516 obj["samplerBorderColor"] = toJSON(tv->samplerBorderColor);
2517 obj["samplerMinLod"] = toJSON(tv->samplerMinLod);
2518 obj["samplerMaxLod"] = toJSON(tv->samplerMaxLod);
2519 obj["samplerLodBias"] = toJSON(tv->samplerLodBias);
2520 obj["samplerCompareFunc"] = toJSON(tv->samplerCompareFunc);
2521 }
2522 break;
2523 }
2524 return obj;
2525}
2526
2527template<> std::shared_ptr<SamplerDescriptor> fromJSON<std::shared_ptr<SamplerDescriptor>>(W<std::shared_ptr<SamplerDescriptor>> v, json &obj) {
2528 enum ::SamplerDescriptor::tag tagType;
2529 std::string tag = obj["tag"];
2530 if (tag == "SamplerDescriptor") {
2531 tagType = ::SamplerDescriptor::tag::SamplerDescriptor;
2532 std::shared_ptr<data::SamplerDescriptor> tv(new data::SamplerDescriptor());
2533 tv->samplerWrapS = fromJSON(W<std::shared_ptr<::EdgeMode>>(), obj["samplerWrapS"]);
2534 tv->samplerWrapT = fromJSON(W<Maybe<std::shared_ptr<::EdgeMode>>>(), obj["samplerWrapT"]);
2535 tv->samplerWrapR = fromJSON(W<Maybe<std::shared_ptr<::EdgeMode>>>(), obj["samplerWrapR"]);
2536 tv->samplerMinFilter = fromJSON(W<std::shared_ptr<::Filter>>(), obj["samplerMinFilter"]);
2537 tv->samplerMagFilter = fromJSON(W<std::shared_ptr<::Filter>>(), obj["samplerMagFilter"]);
2538 tv->samplerBorderColor = fromJSON(W<std::shared_ptr<::Value>>(), obj["samplerBorderColor"]);
2539 tv->samplerMinLod = fromJSON(W<Maybe<Float>>(), obj["samplerMinLod"]);
2540 tv->samplerMaxLod = fromJSON(W<Maybe<Float>>(), obj["samplerMaxLod"]);
2541 tv->samplerLodBias = fromJSON(W<Float>(), obj["samplerLodBias"]);
2542 tv->samplerCompareFunc = fromJSON(W<Maybe<std::shared_ptr<::ComparisonFunction>>>(), obj["samplerCompareFunc"]);
2543 return tv;
2544 }
2545 else throw "unknown constructor: " + tag;
2546 std::shared_ptr<::SamplerDescriptor> o(new ::SamplerDescriptor());
2547 o->tag = tagType;
2548 return o;
2549}
2550
2551template<> json toJSON<std::shared_ptr<TextureDescriptor>>(std::shared_ptr<TextureDescriptor> &v) {
2552 json obj({});
2553 switch (v->tag) {
2554 case ::TextureDescriptor::tag::TextureDescriptor:
2555 obj["tag"] = "TextureDescriptor";
2556 {
2557 std::shared_ptr<data::TextureDescriptor> tv = std::static_pointer_cast<data::TextureDescriptor>(v);
2558 obj["textureType"] = toJSON(tv->textureType);
2559 obj["textureSize"] = toJSON(tv->textureSize);
2560 obj["textureSemantic"] = toJSON(tv->textureSemantic);
2561 obj["textureSampler"] = toJSON(tv->textureSampler);
2562 obj["textureBaseLevel"] = toJSON(tv->textureBaseLevel);
2563 obj["textureMaxLevel"] = toJSON(tv->textureMaxLevel);
2564 }
2565 break;
2566 }
2567 return obj;
2568}
2569
2570template<> std::shared_ptr<TextureDescriptor> fromJSON<std::shared_ptr<TextureDescriptor>>(W<std::shared_ptr<TextureDescriptor>> v, json &obj) {
2571 enum ::TextureDescriptor::tag tagType;
2572 std::string tag = obj["tag"];
2573 if (tag == "TextureDescriptor") {
2574 tagType = ::TextureDescriptor::tag::TextureDescriptor;
2575 std::shared_ptr<data::TextureDescriptor> tv(new data::TextureDescriptor());
2576 tv->textureType = fromJSON(W<std::shared_ptr<::TextureType>>(), obj["textureType"]);
2577 tv->textureSize = fromJSON(W<std::shared_ptr<::Value>>(), obj["textureSize"]);
2578 tv->textureSemantic = fromJSON(W<std::shared_ptr<::ImageSemantic>>(), obj["textureSemantic"]);
2579 tv->textureSampler = fromJSON(W<std::shared_ptr<::SamplerDescriptor>>(), obj["textureSampler"]);
2580 tv->textureBaseLevel = fromJSON(W<Int>(), obj["textureBaseLevel"]);
2581 tv->textureMaxLevel = fromJSON(W<Int>(), obj["textureMaxLevel"]);
2582 return tv;
2583 }
2584 else throw "unknown constructor: " + tag;
2585 std::shared_ptr<::TextureDescriptor> o(new ::TextureDescriptor());
2586 o->tag = tagType;
2587 return o;
2588}
2589
2590template<> json toJSON<std::shared_ptr<Parameter>>(std::shared_ptr<Parameter> &v) {
2591 json obj({});
2592 switch (v->tag) {
2593 case ::Parameter::tag::Parameter:
2594 obj["tag"] = "Parameter";
2595 {
2596 std::shared_ptr<data::Parameter> tv = std::static_pointer_cast<data::Parameter>(v);
2597 obj["name"] = toJSON(tv->name);
2598 obj["ty"] = toJSON(tv->ty);
2599 }
2600 break;
2601 }
2602 return obj;
2603}
2604
2605template<> std::shared_ptr<Parameter> fromJSON<std::shared_ptr<Parameter>>(W<std::shared_ptr<Parameter>> v, json &obj) {
2606 enum ::Parameter::tag tagType;
2607 std::string tag = obj["tag"];
2608 if (tag == "Parameter") {
2609 tagType = ::Parameter::tag::Parameter;
2610 std::shared_ptr<data::Parameter> tv(new data::Parameter());
2611 tv->name = fromJSON(W<String>(), obj["name"]);
2612 tv->ty = fromJSON(W<std::shared_ptr<::InputType>>(), obj["ty"]);
2613 return tv;
2614 }
2615 else throw "unknown constructor: " + tag;
2616 std::shared_ptr<::Parameter> o(new ::Parameter());
2617 o->tag = tagType;
2618 return o;
2619}
2620
2621template<> json toJSON<std::shared_ptr<Program>>(std::shared_ptr<Program> &v) {
2622 json obj({});
2623 switch (v->tag) {
2624 case ::Program::tag::Program:
2625 obj["tag"] = "Program";
2626 {
2627 std::shared_ptr<data::Program> tv = std::static_pointer_cast<data::Program>(v);
2628 obj["programUniforms"] = toJSON(tv->programUniforms);
2629 obj["programStreams"] = toJSON(tv->programStreams);
2630 obj["programInTextures"] = toJSON(tv->programInTextures);
2631 obj["programOutput"] = toJSON(tv->programOutput);
2632 obj["vertexShader"] = toJSON(tv->vertexShader);
2633 obj["geometryShader"] = toJSON(tv->geometryShader);
2634 obj["fragmentShader"] = toJSON(tv->fragmentShader);
2635 }
2636 break;
2637 }
2638 return obj;
2639}
2640
2641template<> std::shared_ptr<Program> fromJSON<std::shared_ptr<Program>>(W<std::shared_ptr<Program>> v, json &obj) {
2642 enum ::Program::tag tagType;
2643 std::string tag = obj["tag"];
2644 if (tag == "Program") {
2645 tagType = ::Program::tag::Program;
2646 std::shared_ptr<data::Program> tv(new data::Program());
2647 tv->programUniforms = fromJSON(W<std::map<::UniformName, std::shared_ptr<::InputType>>>(), obj["programUniforms"]);
2648 tv->programStreams = fromJSON(W<std::map<::UniformName, std::shared_ptr<::Parameter>>>(), obj["programStreams"]);
2649 tv->programInTextures = fromJSON(W<std::map<::UniformName, std::shared_ptr<::InputType>>>(), obj["programInTextures"]);
2650 tv->programOutput = fromJSON(W<std::vector<std::shared_ptr<::Parameter>>>(), obj["programOutput"]);
2651 tv->vertexShader = fromJSON(W<String>(), obj["vertexShader"]);
2652 tv->geometryShader = fromJSON(W<Maybe<String>>(), obj["geometryShader"]);
2653 tv->fragmentShader = fromJSON(W<String>(), obj["fragmentShader"]);
2654 return tv;
2655 }
2656 else throw "unknown constructor: " + tag;
2657 std::shared_ptr<::Program> o(new ::Program());
2658 o->tag = tagType;
2659 return o;
2660}
2661
2662template<> json toJSON<std::shared_ptr<Slot>>(std::shared_ptr<Slot> &v) {
2663 json obj({});
2664 switch (v->tag) {
2665 case ::Slot::tag::Slot:
2666 obj["tag"] = "Slot";
2667 {
2668 std::shared_ptr<data::Slot> tv = std::static_pointer_cast<data::Slot>(v);
2669 obj["slotName"] = toJSON(tv->slotName);
2670 obj["slotStreams"] = toJSON(tv->slotStreams);
2671 obj["slotUniforms"] = toJSON(tv->slotUniforms);
2672 obj["slotPrimitive"] = toJSON(tv->slotPrimitive);
2673 obj["slotPrograms"] = toJSON(tv->slotPrograms);
2674 }
2675 break;
2676 }
2677 return obj;
2678}
2679
2680template<> std::shared_ptr<Slot> fromJSON<std::shared_ptr<Slot>>(W<std::shared_ptr<Slot>> v, json &obj) {
2681 enum ::Slot::tag tagType;
2682 std::string tag = obj["tag"];
2683 if (tag == "Slot") {
2684 tagType = ::Slot::tag::Slot;
2685 std::shared_ptr<data::Slot> tv(new data::Slot());
2686 tv->slotName = fromJSON(W<String>(), obj["slotName"]);
2687 tv->slotStreams = fromJSON(W<std::map<String, std::shared_ptr<::InputType>>>(), obj["slotStreams"]);
2688 tv->slotUniforms = fromJSON(W<std::map<::UniformName, std::shared_ptr<::InputType>>>(), obj["slotUniforms"]);
2689 tv->slotPrimitive = fromJSON(W<std::shared_ptr<::FetchPrimitive>>(), obj["slotPrimitive"]);
2690 tv->slotPrograms = fromJSON(W<std::vector<::ProgramName>>(), obj["slotPrograms"]);
2691 return tv;
2692 }
2693 else throw "unknown constructor: " + tag;
2694 std::shared_ptr<::Slot> o(new ::Slot());
2695 o->tag = tagType;
2696 return o;
2697}
2698
2699template<> json toJSON<std::shared_ptr<StreamData>>(std::shared_ptr<StreamData> &v) {
2700 json obj({});
2701 switch (v->tag) {
2702 case ::StreamData::tag::StreamData:
2703 obj["tag"] = "StreamData";
2704 {
2705 std::shared_ptr<data::StreamData> tv = std::static_pointer_cast<data::StreamData>(v);
2706 obj["streamData"] = toJSON(tv->streamData);
2707 obj["streamType"] = toJSON(tv->streamType);
2708 obj["streamPrimitive"] = toJSON(tv->streamPrimitive);
2709 obj["streamPrograms"] = toJSON(tv->streamPrograms);
2710 }
2711 break;
2712 }
2713 return obj;
2714}
2715
2716template<> std::shared_ptr<StreamData> fromJSON<std::shared_ptr<StreamData>>(W<std::shared_ptr<StreamData>> v, json &obj) {
2717 enum ::StreamData::tag tagType;
2718 std::string tag = obj["tag"];
2719 if (tag == "StreamData") {
2720 tagType = ::StreamData::tag::StreamData;
2721 std::shared_ptr<data::StreamData> tv(new data::StreamData());
2722 tv->streamData = fromJSON(W<std::map<String, std::shared_ptr<::ArrayValue>>>(), obj["streamData"]);
2723 tv->streamType = fromJSON(W<std::map<String, std::shared_ptr<::InputType>>>(), obj["streamType"]);
2724 tv->streamPrimitive = fromJSON(W<std::shared_ptr<::FetchPrimitive>>(), obj["streamPrimitive"]);
2725 tv->streamPrograms = fromJSON(W<std::vector<::ProgramName>>(), obj["streamPrograms"]);
2726 return tv;
2727 }
2728 else throw "unknown constructor: " + tag;
2729 std::shared_ptr<::StreamData> o(new ::StreamData());
2730 o->tag = tagType;
2731 return o;
2732}
2733
2734template<> json toJSON<std::shared_ptr<TargetItem>>(std::shared_ptr<TargetItem> &v) {
2735 json obj({});
2736 switch (v->tag) {
2737 case ::TargetItem::tag::TargetItem:
2738 obj["tag"] = "TargetItem";
2739 {
2740 std::shared_ptr<data::TargetItem> tv = std::static_pointer_cast<data::TargetItem>(v);
2741 obj["targetSemantic"] = toJSON(tv->targetSemantic);
2742 obj["targetRef"] = toJSON(tv->targetRef);
2743 }
2744 break;
2745 }
2746 return obj;
2747}
2748
2749template<> std::shared_ptr<TargetItem> fromJSON<std::shared_ptr<TargetItem>>(W<std::shared_ptr<TargetItem>> v, json &obj) {
2750 enum ::TargetItem::tag tagType;
2751 std::string tag = obj["tag"];
2752 if (tag == "TargetItem") {
2753 tagType = ::TargetItem::tag::TargetItem;
2754 std::shared_ptr<data::TargetItem> tv(new data::TargetItem());
2755 tv->targetSemantic = fromJSON(W<std::shared_ptr<::ImageSemantic>>(), obj["targetSemantic"]);
2756 tv->targetRef = fromJSON(W<Maybe<std::shared_ptr<::ImageRef>>>(), obj["targetRef"]);
2757 return tv;
2758 }
2759 else throw "unknown constructor: " + tag;
2760 std::shared_ptr<::TargetItem> o(new ::TargetItem());
2761 o->tag = tagType;
2762 return o;
2763}
2764
2765template<> json toJSON<std::shared_ptr<RenderTarget>>(std::shared_ptr<RenderTarget> &v) {
2766 json obj({});
2767 switch (v->tag) {
2768 case ::RenderTarget::tag::RenderTarget:
2769 obj["tag"] = "RenderTarget";
2770 {
2771 std::shared_ptr<data::RenderTarget> tv = std::static_pointer_cast<data::RenderTarget>(v);
2772 obj["renderTargets"] = toJSON(tv->renderTargets);
2773 }
2774 break;
2775 }
2776 return obj;
2777}
2778
2779template<> std::shared_ptr<RenderTarget> fromJSON<std::shared_ptr<RenderTarget>>(W<std::shared_ptr<RenderTarget>> v, json &obj) {
2780 enum ::RenderTarget::tag tagType;
2781 std::string tag = obj["tag"];
2782 if (tag == "RenderTarget") {
2783 tagType = ::RenderTarget::tag::RenderTarget;
2784 std::shared_ptr<data::RenderTarget> tv(new data::RenderTarget());
2785 tv->renderTargets = fromJSON(W<std::vector<std::shared_ptr<::TargetItem>>>(), obj["renderTargets"]);
2786 return tv;
2787 }
2788 else throw "unknown constructor: " + tag;
2789 std::shared_ptr<::RenderTarget> o(new ::RenderTarget());
2790 o->tag = tagType;
2791 return o;
2792}
2793
2794template<> json toJSON<std::shared_ptr<Backend>>(std::shared_ptr<Backend> &v) {
2795 json obj({});
2796 switch (v->tag) {
2797 case ::Backend::tag::WebGL1:
2798 obj["tag"] = "WebGL1";
2799 break;
2800 case ::Backend::tag::OpenGL33:
2801 obj["tag"] = "OpenGL33";
2802 break;
2803 }
2804 return obj;
2805}
2806
2807template<> std::shared_ptr<Backend> fromJSON<std::shared_ptr<Backend>>(W<std::shared_ptr<Backend>> v, json &obj) {
2808 enum ::Backend::tag tagType;
2809 std::string tag = obj["tag"];
2810 if (tag == "WebGL1") {
2811 tagType = ::Backend::tag::WebGL1;
2812 }
2813 else if (tag == "OpenGL33") {
2814 tagType = ::Backend::tag::OpenGL33;
2815 }
2816 else throw "unknown constructor: " + tag;
2817 std::shared_ptr<::Backend> o(new ::Backend());
2818 o->tag = tagType;
2819 return o;
2820}
2821
2822template<> json toJSON<std::shared_ptr<Pipeline>>(std::shared_ptr<Pipeline> &v) {
2823 json obj({});
2824 switch (v->tag) {
2825 case ::Pipeline::tag::Pipeline:
2826 obj["tag"] = "Pipeline";
2827 {
2828 std::shared_ptr<data::Pipeline> tv = std::static_pointer_cast<data::Pipeline>(v);
2829 obj["backend"] = toJSON(tv->backend);
2830 obj["textures"] = toJSON(tv->textures);
2831 obj["samplers"] = toJSON(tv->samplers);
2832 obj["targets"] = toJSON(tv->targets);
2833 obj["programs"] = toJSON(tv->programs);
2834 obj["slots"] = toJSON(tv->slots);
2835 obj["streams"] = toJSON(tv->streams);
2836 obj["commands"] = toJSON(tv->commands);
2837 }
2838 break;
2839 }
2840 return obj;
2841}
2842
2843template<> std::shared_ptr<Pipeline> fromJSON<std::shared_ptr<Pipeline>>(W<std::shared_ptr<Pipeline>> v, json &obj) {
2844 enum ::Pipeline::tag tagType;
2845 std::string tag = obj["tag"];
2846 if (tag == "Pipeline") {
2847 tagType = ::Pipeline::tag::Pipeline;
2848 std::shared_ptr<data::Pipeline> tv(new data::Pipeline());
2849 tv->backend = fromJSON(W<std::shared_ptr<::Backend>>(), obj["backend"]);
2850 tv->textures = fromJSON(W<std::vector<std::shared_ptr<::TextureDescriptor>>>(), obj["textures"]);
2851 tv->samplers = fromJSON(W<std::vector<std::shared_ptr<::SamplerDescriptor>>>(), obj["samplers"]);
2852 tv->targets = fromJSON(W<std::vector<std::shared_ptr<::RenderTarget>>>(), obj["targets"]);
2853 tv->programs = fromJSON(W<std::vector<std::shared_ptr<::Program>>>(), obj["programs"]);
2854 tv->slots = fromJSON(W<std::vector<std::shared_ptr<::Slot>>>(), obj["slots"]);
2855 tv->streams = fromJSON(W<std::vector<std::shared_ptr<::StreamData>>>(), obj["streams"]);
2856 tv->commands = fromJSON(W<std::vector<std::shared_ptr<::Command>>>(), obj["commands"]);
2857 return tv;
2858 }
2859 else throw "unknown constructor: " + tag;
2860 std::shared_ptr<::Pipeline> o(new ::Pipeline());
2861 o->tag = tagType;
2862 return o;
2863}
2864
diff --git a/ddl/out/IR.hpp b/ddl/out/IR.hpp
new file mode 100644
index 0000000..3c6055f
--- /dev/null
+++ b/ddl/out/IR.hpp
@@ -0,0 +1,1070 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.420877000000Z
3
4#ifndef HEADER_IR_H
5#define HEADER_IR_H
6
7#include "RT.hpp"
8
9
10typedef Int StreamName;
11
12typedef Int ProgramName;
13
14typedef Int TextureName;
15
16typedef Int SamplerName;
17
18typedef String UniformName;
19
20typedef Int SlotName;
21
22typedef Int FrameBufferComponent;
23
24typedef Int TextureUnit;
25
26typedef Int RenderTargetName;
27
28typedef std::map<::UniformName, ::TextureUnit> TextureUnitMapping;
29
30class ArrayValue {
31 public:
32 enum class tag {
33 VBoolArray,
34 VIntArray,
35 VWordArray,
36 VFloatArray
37 } tag;
38};
39namespace data {
40 class VBoolArray : public ::ArrayValue {
41 public:
42 std::vector<Bool> _0;
43 VBoolArray() { tag = tag::VBoolArray; }
44 };
45 class VIntArray : public ::ArrayValue {
46 public:
47 std::vector<Int32> _0;
48 VIntArray() { tag = tag::VIntArray; }
49 };
50 class VWordArray : public ::ArrayValue {
51 public:
52 std::vector<Word32> _0;
53 VWordArray() { tag = tag::VWordArray; }
54 };
55 class VFloatArray : public ::ArrayValue {
56 public:
57 std::vector<Float> _0;
58 VFloatArray() { tag = tag::VFloatArray; }
59 };
60}
61class Value {
62 public:
63 enum class tag {
64 VBool,
65 VV2B,
66 VV3B,
67 VV4B,
68 VWord,
69 VV2U,
70 VV3U,
71 VV4U,
72 VInt,
73 VV2I,
74 VV3I,
75 VV4I,
76 VFloat,
77 VV2F,
78 VV3F,
79 VV4F,
80 VM22F,
81 VM23F,
82 VM24F,
83 VM32F,
84 VM33F,
85 VM34F,
86 VM42F,
87 VM43F,
88 VM44F
89 } tag;
90};
91namespace data {
92 class VBool : public ::Value {
93 public:
94 Bool _0;
95 VBool() { tag = tag::VBool; }
96 };
97 class VV2B : public ::Value {
98 public:
99 V2B _0;
100 VV2B() { tag = tag::VV2B; }
101 };
102 class VV3B : public ::Value {
103 public:
104 V3B _0;
105 VV3B() { tag = tag::VV3B; }
106 };
107 class VV4B : public ::Value {
108 public:
109 V4B _0;
110 VV4B() { tag = tag::VV4B; }
111 };
112 class VWord : public ::Value {
113 public:
114 Word32 _0;
115 VWord() { tag = tag::VWord; }
116 };
117 class VV2U : public ::Value {
118 public:
119 V2U _0;
120 VV2U() { tag = tag::VV2U; }
121 };
122 class VV3U : public ::Value {
123 public:
124 V3U _0;
125 VV3U() { tag = tag::VV3U; }
126 };
127 class VV4U : public ::Value {
128 public:
129 V4U _0;
130 VV4U() { tag = tag::VV4U; }
131 };
132 class VInt : public ::Value {
133 public:
134 Int32 _0;
135 VInt() { tag = tag::VInt; }
136 };
137 class VV2I : public ::Value {
138 public:
139 V2I _0;
140 VV2I() { tag = tag::VV2I; }
141 };
142 class VV3I : public ::Value {
143 public:
144 V3I _0;
145 VV3I() { tag = tag::VV3I; }
146 };
147 class VV4I : public ::Value {
148 public:
149 V4I _0;
150 VV4I() { tag = tag::VV4I; }
151 };
152 class VFloat : public ::Value {
153 public:
154 Float _0;
155 VFloat() { tag = tag::VFloat; }
156 };
157 class VV2F : public ::Value {
158 public:
159 V2F _0;
160 VV2F() { tag = tag::VV2F; }
161 };
162 class VV3F : public ::Value {
163 public:
164 V3F _0;
165 VV3F() { tag = tag::VV3F; }
166 };
167 class VV4F : public ::Value {
168 public:
169 V4F _0;
170 VV4F() { tag = tag::VV4F; }
171 };
172 class VM22F : public ::Value {
173 public:
174 M22F _0;
175 VM22F() { tag = tag::VM22F; }
176 };
177 class VM23F : public ::Value {
178 public:
179 M23F _0;
180 VM23F() { tag = tag::VM23F; }
181 };
182 class VM24F : public ::Value {
183 public:
184 M24F _0;
185 VM24F() { tag = tag::VM24F; }
186 };
187 class VM32F : public ::Value {
188 public:
189 M32F _0;
190 VM32F() { tag = tag::VM32F; }
191 };
192 class VM33F : public ::Value {
193 public:
194 M33F _0;
195 VM33F() { tag = tag::VM33F; }
196 };
197 class VM34F : public ::Value {
198 public:
199 M34F _0;
200 VM34F() { tag = tag::VM34F; }
201 };
202 class VM42F : public ::Value {
203 public:
204 M42F _0;
205 VM42F() { tag = tag::VM42F; }
206 };
207 class VM43F : public ::Value {
208 public:
209 M43F _0;
210 VM43F() { tag = tag::VM43F; }
211 };
212 class VM44F : public ::Value {
213 public:
214 M44F _0;
215 VM44F() { tag = tag::VM44F; }
216 };
217}
218class InputType {
219 public:
220 enum class tag {
221 Bool,
222 V2B,
223 V3B,
224 V4B,
225 Word,
226 V2U,
227 V3U,
228 V4U,
229 Int,
230 V2I,
231 V3I,
232 V4I,
233 Float,
234 V2F,
235 V3F,
236 V4F,
237 M22F,
238 M23F,
239 M24F,
240 M32F,
241 M33F,
242 M34F,
243 M42F,
244 M43F,
245 M44F,
246 STexture1D,
247 STexture2D,
248 STextureCube,
249 STexture1DArray,
250 STexture2DArray,
251 STexture2DRect,
252 FTexture1D,
253 FTexture2D,
254 FTexture3D,
255 FTextureCube,
256 FTexture1DArray,
257 FTexture2DArray,
258 FTexture2DMS,
259 FTexture2DMSArray,
260 FTextureBuffer,
261 FTexture2DRect,
262 ITexture1D,
263 ITexture2D,
264 ITexture3D,
265 ITextureCube,
266 ITexture1DArray,
267 ITexture2DArray,
268 ITexture2DMS,
269 ITexture2DMSArray,
270 ITextureBuffer,
271 ITexture2DRect,
272 UTexture1D,
273 UTexture2D,
274 UTexture3D,
275 UTextureCube,
276 UTexture1DArray,
277 UTexture2DArray,
278 UTexture2DMS,
279 UTexture2DMSArray,
280 UTextureBuffer,
281 UTexture2DRect
282 } tag;
283};
284namespace data {
285}
286class PointSpriteCoordOrigin {
287 public:
288 enum class tag {
289 LowerLeft,
290 UpperLeft
291 } tag;
292};
293namespace data {
294}
295class PointSize {
296 public:
297 enum class tag {
298 PointSize,
299 ProgramPointSize
300 } tag;
301};
302namespace data {
303 class PointSize : public ::PointSize {
304 public:
305 Float _0;
306 PointSize() { tag = tag::PointSize; }
307 };
308}
309class PolygonOffset {
310 public:
311 enum class tag {
312 NoOffset,
313 Offset
314 } tag;
315};
316namespace data {
317 class Offset : public ::PolygonOffset {
318 public:
319 Float _0;
320 Float _1;
321 Offset() { tag = tag::Offset; }
322 };
323}
324class FrontFace {
325 public:
326 enum class tag {
327 CCW,
328 CW
329 } tag;
330};
331namespace data {
332}
333class PolygonMode {
334 public:
335 enum class tag {
336 PolygonPoint,
337 PolygonLine,
338 PolygonFill
339 } tag;
340};
341namespace data {
342 class PolygonPoint : public ::PolygonMode {
343 public:
344 std::shared_ptr<::PointSize> _0;
345 PolygonPoint() { tag = tag::PolygonPoint; }
346 };
347 class PolygonLine : public ::PolygonMode {
348 public:
349 Float _0;
350 PolygonLine() { tag = tag::PolygonLine; }
351 };
352}
353class ProvokingVertex {
354 public:
355 enum class tag {
356 FirstVertex,
357 LastVertex
358 } tag;
359};
360namespace data {
361}
362class CullMode {
363 public:
364 enum class tag {
365 CullNone,
366 CullFront,
367 CullBack
368 } tag;
369};
370namespace data {
371 class CullFront : public ::CullMode {
372 public:
373 std::shared_ptr<::FrontFace> _0;
374 CullFront() { tag = tag::CullFront; }
375 };
376 class CullBack : public ::CullMode {
377 public:
378 std::shared_ptr<::FrontFace> _0;
379 CullBack() { tag = tag::CullBack; }
380 };
381}
382class ComparisonFunction {
383 public:
384 enum class tag {
385 Never,
386 Less,
387 Equal,
388 Lequal,
389 Greater,
390 Notequal,
391 Gequal,
392 Always
393 } tag;
394};
395namespace data {
396}
397typedef ComparisonFunction DepthFunction;
398
399class StencilOperation {
400 public:
401 enum class tag {
402 OpZero,
403 OpKeep,
404 OpReplace,
405 OpIncr,
406 OpIncrWrap,
407 OpDecr,
408 OpDecrWrap,
409 OpInvert
410 } tag;
411};
412namespace data {
413}
414class BlendEquation {
415 public:
416 enum class tag {
417 FuncAdd,
418 FuncSubtract,
419 FuncReverseSubtract,
420 Min,
421 Max
422 } tag;
423};
424namespace data {
425}
426class BlendingFactor {
427 public:
428 enum class tag {
429 Zero,
430 One,
431 SrcColor,
432 OneMinusSrcColor,
433 DstColor,
434 OneMinusDstColor,
435 SrcAlpha,
436 OneMinusSrcAlpha,
437 DstAlpha,
438 OneMinusDstAlpha,
439 ConstantColor,
440 OneMinusConstantColor,
441 ConstantAlpha,
442 OneMinusConstantAlpha,
443 SrcAlphaSaturate
444 } tag;
445};
446namespace data {
447}
448class LogicOperation {
449 public:
450 enum class tag {
451 Clear,
452 And,
453 AndReverse,
454 Copy,
455 AndInverted,
456 Noop,
457 Xor,
458 Or,
459 Nor,
460 Equiv,
461 Invert,
462 OrReverse,
463 CopyInverted,
464 OrInverted,
465 Nand,
466 Set
467 } tag;
468};
469namespace data {
470}
471class StencilOps {
472 public:
473 enum class tag {
474 StencilOps
475 } tag;
476};
477namespace data {
478 class StencilOps : public ::StencilOps {
479 public:
480 std::shared_ptr<::StencilOperation> frontStencilOp;
481 std::shared_ptr<::StencilOperation> backStencilOp;
482 StencilOps() { tag = tag::StencilOps; }
483 };
484}
485class StencilTest {
486 public:
487 enum class tag {
488 StencilTest
489 } tag;
490};
491namespace data {
492 class StencilTest : public ::StencilTest {
493 public:
494 std::shared_ptr<::ComparisonFunction> stencilComparision;
495 Int32 stencilReference;
496 Word32 stencilMask;
497 StencilTest() { tag = tag::StencilTest; }
498 };
499}
500class StencilTests {
501 public:
502 enum class tag {
503 StencilTests
504 } tag;
505};
506namespace data {
507 class StencilTests : public ::StencilTests {
508 public:
509 std::shared_ptr<::StencilTest> _0;
510 std::shared_ptr<::StencilTest> _1;
511 StencilTests() { tag = tag::StencilTests; }
512 };
513}
514class FetchPrimitive {
515 public:
516 enum class tag {
517 Points,
518 Lines,
519 Triangles,
520 LinesAdjacency,
521 TrianglesAdjacency
522 } tag;
523};
524namespace data {
525}
526class OutputPrimitive {
527 public:
528 enum class tag {
529 TrianglesOutput,
530 LinesOutput,
531 PointsOutput
532 } tag;
533};
534namespace data {
535}
536class ColorArity {
537 public:
538 enum class tag {
539 Red,
540 RG,
541 RGB,
542 RGBA
543 } tag;
544};
545namespace data {
546}
547class Blending {
548 public:
549 enum class tag {
550 NoBlending,
551 BlendLogicOp,
552 Blend
553 } tag;
554};
555namespace data {
556 class BlendLogicOp : public ::Blending {
557 public:
558 std::shared_ptr<::LogicOperation> _0;
559 BlendLogicOp() { tag = tag::BlendLogicOp; }
560 };
561 class Blend : public ::Blending {
562 public:
563 std::shared_ptr<::BlendEquation> colorEqSrc;
564 std::shared_ptr<::BlendEquation> alphaEqSrc;
565 std::shared_ptr<::BlendingFactor> colorFSrc;
566 std::shared_ptr<::BlendingFactor> colorFDst;
567 std::shared_ptr<::BlendingFactor> alphaFSrc;
568 std::shared_ptr<::BlendingFactor> alphaFDst;
569 V4F color;
570 Blend() { tag = tag::Blend; }
571 };
572}
573class RasterContext {
574 public:
575 enum class tag {
576 PointCtx,
577 LineCtx,
578 TriangleCtx
579 } tag;
580};
581namespace data {
582 class PointCtx : public ::RasterContext {
583 public:
584 std::shared_ptr<::PointSize> _0;
585 Float _1;
586 std::shared_ptr<::PointSpriteCoordOrigin> _2;
587 PointCtx() { tag = tag::PointCtx; }
588 };
589 class LineCtx : public ::RasterContext {
590 public:
591 Float _0;
592 std::shared_ptr<::ProvokingVertex> _1;
593 LineCtx() { tag = tag::LineCtx; }
594 };
595 class TriangleCtx : public ::RasterContext {
596 public:
597 std::shared_ptr<::CullMode> _0;
598 std::shared_ptr<::PolygonMode> _1;
599 std::shared_ptr<::PolygonOffset> _2;
600 std::shared_ptr<::ProvokingVertex> _3;
601 TriangleCtx() { tag = tag::TriangleCtx; }
602 };
603}
604class FragmentOperation {
605 public:
606 enum class tag {
607 DepthOp,
608 StencilOp,
609 ColorOp
610 } tag;
611};
612namespace data {
613 class DepthOp : public ::FragmentOperation {
614 public:
615 std::shared_ptr<::DepthFunction> _0;
616 Bool _1;
617 DepthOp() { tag = tag::DepthOp; }
618 };
619 class StencilOp : public ::FragmentOperation {
620 public:
621 std::shared_ptr<::StencilTests> _0;
622 std::shared_ptr<::StencilOps> _1;
623 std::shared_ptr<::StencilOps> _2;
624 StencilOp() { tag = tag::StencilOp; }
625 };
626 class ColorOp : public ::FragmentOperation {
627 public:
628 std::shared_ptr<::Blending> _0;
629 std::shared_ptr<::Value> _1;
630 ColorOp() { tag = tag::ColorOp; }
631 };
632}
633class AccumulationContext {
634 public:
635 enum class tag {
636 AccumulationContext
637 } tag;
638};
639namespace data {
640 class AccumulationContext : public ::AccumulationContext {
641 public:
642 Maybe<String> accViewportName;
643 std::vector<std::shared_ptr<::FragmentOperation>> accOperations;
644 AccumulationContext() { tag = tag::AccumulationContext; }
645 };
646}
647class TextureDataType {
648 public:
649 enum class tag {
650 FloatT,
651 IntT,
652 WordT,
653 ShadowT
654 } tag;
655};
656namespace data {
657 class FloatT : public ::TextureDataType {
658 public:
659 std::shared_ptr<::ColorArity> _0;
660 FloatT() { tag = tag::FloatT; }
661 };
662 class IntT : public ::TextureDataType {
663 public:
664 std::shared_ptr<::ColorArity> _0;
665 IntT() { tag = tag::IntT; }
666 };
667 class WordT : public ::TextureDataType {
668 public:
669 std::shared_ptr<::ColorArity> _0;
670 WordT() { tag = tag::WordT; }
671 };
672}
673class TextureType {
674 public:
675 enum class tag {
676 Texture1D,
677 Texture2D,
678 Texture3D,
679 TextureCube,
680 TextureRect,
681 Texture2DMS,
682 TextureBuffer
683 } tag;
684};
685namespace data {
686 class Texture1D : public ::TextureType {
687 public:
688 std::shared_ptr<::TextureDataType> _0;
689 Int _1;
690 Texture1D() { tag = tag::Texture1D; }
691 };
692 class Texture2D : public ::TextureType {
693 public:
694 std::shared_ptr<::TextureDataType> _0;
695 Int _1;
696 Texture2D() { tag = tag::Texture2D; }
697 };
698 class Texture3D : public ::TextureType {
699 public:
700 std::shared_ptr<::TextureDataType> _0;
701 Texture3D() { tag = tag::Texture3D; }
702 };
703 class TextureCube : public ::TextureType {
704 public:
705 std::shared_ptr<::TextureDataType> _0;
706 TextureCube() { tag = tag::TextureCube; }
707 };
708 class TextureRect : public ::TextureType {
709 public:
710 std::shared_ptr<::TextureDataType> _0;
711 TextureRect() { tag = tag::TextureRect; }
712 };
713 class Texture2DMS : public ::TextureType {
714 public:
715 std::shared_ptr<::TextureDataType> _0;
716 Int _1;
717 Int _2;
718 Bool _3;
719 Texture2DMS() { tag = tag::Texture2DMS; }
720 };
721 class TextureBuffer : public ::TextureType {
722 public:
723 std::shared_ptr<::TextureDataType> _0;
724 TextureBuffer() { tag = tag::TextureBuffer; }
725 };
726}
727class MipMap {
728 public:
729 enum class tag {
730 Mip,
731 NoMip,
732 AutoMip
733 } tag;
734};
735namespace data {
736 class Mip : public ::MipMap {
737 public:
738 Int _0;
739 Int _1;
740 Mip() { tag = tag::Mip; }
741 };
742 class AutoMip : public ::MipMap {
743 public:
744 Int _0;
745 Int _1;
746 AutoMip() { tag = tag::AutoMip; }
747 };
748}
749class Filter {
750 public:
751 enum class tag {
752 Nearest,
753 Linear,
754 NearestMipmapNearest,
755 NearestMipmapLinear,
756 LinearMipmapNearest,
757 LinearMipmapLinear
758 } tag;
759};
760namespace data {
761}
762class EdgeMode {
763 public:
764 enum class tag {
765 Repeat,
766 MirroredRepeat,
767 ClampToEdge,
768 ClampToBorder
769 } tag;
770};
771namespace data {
772}
773class ImageSemantic {
774 public:
775 enum class tag {
776 Depth,
777 Stencil,
778 Color
779 } tag;
780};
781namespace data {
782}
783class ImageRef {
784 public:
785 enum class tag {
786 TextureImage,
787 Framebuffer
788 } tag;
789};
790namespace data {
791 class TextureImage : public ::ImageRef {
792 public:
793 ::TextureName _0;
794 Int _1;
795 Maybe<Int> _2;
796 TextureImage() { tag = tag::TextureImage; }
797 };
798 class Framebuffer : public ::ImageRef {
799 public:
800 std::shared_ptr<::ImageSemantic> _0;
801 Framebuffer() { tag = tag::Framebuffer; }
802 };
803}
804class ClearImage {
805 public:
806 enum class tag {
807 ClearImage
808 } tag;
809};
810namespace data {
811 class ClearImage : public ::ClearImage {
812 public:
813 std::shared_ptr<::ImageSemantic> imageSemantic;
814 std::shared_ptr<::Value> clearValue;
815 ClearImage() { tag = tag::ClearImage; }
816 };
817}
818class Command {
819 public:
820 enum class tag {
821 SetRasterContext,
822 SetAccumulationContext,
823 SetRenderTarget,
824 SetProgram,
825 SetSamplerUniform,
826 SetTexture,
827 SetSampler,
828 RenderSlot,
829 RenderStream,
830 ClearRenderTarget,
831 GenerateMipMap,
832 SaveImage,
833 LoadImage
834 } tag;
835};
836namespace data {
837 class SetRasterContext : public ::Command {
838 public:
839 std::shared_ptr<::RasterContext> _0;
840 SetRasterContext() { tag = tag::SetRasterContext; }
841 };
842 class SetAccumulationContext : public ::Command {
843 public:
844 std::shared_ptr<::AccumulationContext> _0;
845 SetAccumulationContext() { tag = tag::SetAccumulationContext; }
846 };
847 class SetRenderTarget : public ::Command {
848 public:
849 ::RenderTargetName _0;
850 SetRenderTarget() { tag = tag::SetRenderTarget; }
851 };
852 class SetProgram : public ::Command {
853 public:
854 ::ProgramName _0;
855 SetProgram() { tag = tag::SetProgram; }
856 };
857 class SetSamplerUniform : public ::Command {
858 public:
859 ::UniformName _0;
860 ::TextureUnit _1;
861 SetSamplerUniform() { tag = tag::SetSamplerUniform; }
862 };
863 class SetTexture : public ::Command {
864 public:
865 ::TextureUnit _0;
866 ::TextureName _1;
867 SetTexture() { tag = tag::SetTexture; }
868 };
869 class SetSampler : public ::Command {
870 public:
871 ::TextureUnit _0;
872 Maybe<::SamplerName> _1;
873 SetSampler() { tag = tag::SetSampler; }
874 };
875 class RenderSlot : public ::Command {
876 public:
877 ::SlotName _0;
878 RenderSlot() { tag = tag::RenderSlot; }
879 };
880 class RenderStream : public ::Command {
881 public:
882 ::StreamName _0;
883 RenderStream() { tag = tag::RenderStream; }
884 };
885 class ClearRenderTarget : public ::Command {
886 public:
887 std::vector<std::shared_ptr<::ClearImage>> _0;
888 ClearRenderTarget() { tag = tag::ClearRenderTarget; }
889 };
890 class GenerateMipMap : public ::Command {
891 public:
892 ::TextureUnit _0;
893 GenerateMipMap() { tag = tag::GenerateMipMap; }
894 };
895 class SaveImage : public ::Command {
896 public:
897 ::FrameBufferComponent _0;
898 std::shared_ptr<::ImageRef> _1;
899 SaveImage() { tag = tag::SaveImage; }
900 };
901 class LoadImage : public ::Command {
902 public:
903 std::shared_ptr<::ImageRef> _0;
904 ::FrameBufferComponent _1;
905 LoadImage() { tag = tag::LoadImage; }
906 };
907}
908class SamplerDescriptor {
909 public:
910 enum class tag {
911 SamplerDescriptor
912 } tag;
913};
914namespace data {
915 class SamplerDescriptor : public ::SamplerDescriptor {
916 public:
917 std::shared_ptr<::EdgeMode> samplerWrapS;
918 Maybe<std::shared_ptr<::EdgeMode>> samplerWrapT;
919 Maybe<std::shared_ptr<::EdgeMode>> samplerWrapR;
920 std::shared_ptr<::Filter> samplerMinFilter;
921 std::shared_ptr<::Filter> samplerMagFilter;
922 std::shared_ptr<::Value> samplerBorderColor;
923 Maybe<Float> samplerMinLod;
924 Maybe<Float> samplerMaxLod;
925 Float samplerLodBias;
926 Maybe<std::shared_ptr<::ComparisonFunction>> samplerCompareFunc;
927 SamplerDescriptor() { tag = tag::SamplerDescriptor; }
928 };
929}
930class TextureDescriptor {
931 public:
932 enum class tag {
933 TextureDescriptor
934 } tag;
935};
936namespace data {
937 class TextureDescriptor : public ::TextureDescriptor {
938 public:
939 std::shared_ptr<::TextureType> textureType;
940 std::shared_ptr<::Value> textureSize;
941 std::shared_ptr<::ImageSemantic> textureSemantic;
942 std::shared_ptr<::SamplerDescriptor> textureSampler;
943 Int textureBaseLevel;
944 Int textureMaxLevel;
945 TextureDescriptor() { tag = tag::TextureDescriptor; }
946 };
947}
948class Parameter {
949 public:
950 enum class tag {
951 Parameter
952 } tag;
953};
954namespace data {
955 class Parameter : public ::Parameter {
956 public:
957 String name;
958 std::shared_ptr<::InputType> ty;
959 Parameter() { tag = tag::Parameter; }
960 };
961}
962class Program {
963 public:
964 enum class tag {
965 Program
966 } tag;
967};
968namespace data {
969 class Program : public ::Program {
970 public:
971 std::map<::UniformName, std::shared_ptr<::InputType>> programUniforms;
972 std::map<::UniformName, std::shared_ptr<::Parameter>> programStreams;
973 std::map<::UniformName, std::shared_ptr<::InputType>> programInTextures;
974 std::vector<std::shared_ptr<::Parameter>> programOutput;
975 String vertexShader;
976 Maybe<String> geometryShader;
977 String fragmentShader;
978 Program() { tag = tag::Program; }
979 };
980}
981class Slot {
982 public:
983 enum class tag {
984 Slot
985 } tag;
986};
987namespace data {
988 class Slot : public ::Slot {
989 public:
990 String slotName;
991 std::map<String, std::shared_ptr<::InputType>> slotStreams;
992 std::map<::UniformName, std::shared_ptr<::InputType>> slotUniforms;
993 std::shared_ptr<::FetchPrimitive> slotPrimitive;
994 std::vector<::ProgramName> slotPrograms;
995 Slot() { tag = tag::Slot; }
996 };
997}
998class StreamData {
999 public:
1000 enum class tag {
1001 StreamData
1002 } tag;
1003};
1004namespace data {
1005 class StreamData : public ::StreamData {
1006 public:
1007 std::map<String, std::shared_ptr<::ArrayValue>> streamData;
1008 std::map<String, std::shared_ptr<::InputType>> streamType;
1009 std::shared_ptr<::FetchPrimitive> streamPrimitive;
1010 std::vector<::ProgramName> streamPrograms;
1011 StreamData() { tag = tag::StreamData; }
1012 };
1013}
1014class TargetItem {
1015 public:
1016 enum class tag {
1017 TargetItem
1018 } tag;
1019};
1020namespace data {
1021 class TargetItem : public ::TargetItem {
1022 public:
1023 std::shared_ptr<::ImageSemantic> targetSemantic;
1024 Maybe<std::shared_ptr<::ImageRef>> targetRef;
1025 TargetItem() { tag = tag::TargetItem; }
1026 };
1027}
1028class RenderTarget {
1029 public:
1030 enum class tag {
1031 RenderTarget
1032 } tag;
1033};
1034namespace data {
1035 class RenderTarget : public ::RenderTarget {
1036 public:
1037 std::vector<std::shared_ptr<::TargetItem>> renderTargets;
1038 RenderTarget() { tag = tag::RenderTarget; }
1039 };
1040}
1041class Backend {
1042 public:
1043 enum class tag {
1044 WebGL1,
1045 OpenGL33
1046 } tag;
1047};
1048namespace data {
1049}
1050class Pipeline {
1051 public:
1052 enum class tag {
1053 Pipeline
1054 } tag;
1055};
1056namespace data {
1057 class Pipeline : public ::Pipeline {
1058 public:
1059 std::shared_ptr<::Backend> backend;
1060 std::vector<std::shared_ptr<::TextureDescriptor>> textures;
1061 std::vector<std::shared_ptr<::SamplerDescriptor>> samplers;
1062 std::vector<std::shared_ptr<::RenderTarget>> targets;
1063 std::vector<std::shared_ptr<::Program>> programs;
1064 std::vector<std::shared_ptr<::Slot>> slots;
1065 std::vector<std::shared_ptr<::StreamData>> streams;
1066 std::vector<std::shared_ptr<::Command>> commands;
1067 Pipeline() { tag = tag::Pipeline; }
1068 };
1069}
1070#endif
diff --git a/ddl/out/IR.hs b/ddl/out/IR.hs
new file mode 100644
index 0000000..a788161
--- /dev/null
+++ b/ddl/out/IR.hs
@@ -0,0 +1,1608 @@
1-- generated file, do not modify!
2-- 2015-12-21T12:00:19.420877000000Z
3
4{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
5module IR where
6
7import Data.Int
8import Data.Word
9import Data.Map
10import Data.Vector (Vector(..))
11import Linear
12
13import Data.Text
14import Data.Aeson hiding (Value,Bool)
15import Data.Aeson.Types hiding (Value,Bool)
16import Control.Monad
17
18
19type StreamName = Int
20
21type ProgramName = Int
22
23type TextureName = Int
24
25type SamplerName = Int
26
27type UniformName = String
28
29type SlotName = Int
30
31type FrameBufferComponent = Int
32
33type TextureUnit = Int
34
35type RenderTargetName = Int
36
37type TextureUnitMapping = Map UniformName TextureUnit
38
39data ArrayValue
40 = VBoolArray (Vector Bool)
41 | VIntArray (Vector Int32)
42 | VWordArray (Vector Word32)
43 | VFloatArray (Vector Float)
44 deriving (Show, Eq, Ord)
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 deriving (Show, Eq, Ord)
73
74data InputType
75 = Bool
76 | V2B
77 | V3B
78 | V4B
79 | Word
80 | V2U
81 | V3U
82 | V4U
83 | Int
84 | V2I
85 | V3I
86 | V4I
87 | Float
88 | V2F
89 | V3F
90 | V4F
91 | M22F
92 | M23F
93 | M24F
94 | M32F
95 | M33F
96 | M34F
97 | M42F
98 | M43F
99 | M44F
100 | STexture1D
101 | STexture2D
102 | STextureCube
103 | STexture1DArray
104 | STexture2DArray
105 | STexture2DRect
106 | FTexture1D
107 | FTexture2D
108 | FTexture3D
109 | FTextureCube
110 | FTexture1DArray
111 | FTexture2DArray
112 | FTexture2DMS
113 | FTexture2DMSArray
114 | FTextureBuffer
115 | FTexture2DRect
116 | ITexture1D
117 | ITexture2D
118 | ITexture3D
119 | ITextureCube
120 | ITexture1DArray
121 | ITexture2DArray
122 | ITexture2DMS
123 | ITexture2DMSArray
124 | ITextureBuffer
125 | ITexture2DRect
126 | UTexture1D
127 | UTexture2D
128 | UTexture3D
129 | UTextureCube
130 | UTexture1DArray
131 | UTexture2DArray
132 | UTexture2DMS
133 | UTexture2DMSArray
134 | UTextureBuffer
135 | UTexture2DRect
136 deriving (Show, Eq, Ord)
137
138data PointSpriteCoordOrigin
139 = LowerLeft
140 | UpperLeft
141 deriving (Show, Eq, Ord)
142
143data PointSize
144 = PointSize Float
145 | ProgramPointSize
146 deriving (Show, Eq, Ord)
147
148data PolygonOffset
149 = NoOffset
150 | Offset Float Float
151 deriving (Show, Eq, Ord)
152
153data FrontFace
154 = CCW
155 | CW
156 deriving (Show, Eq, Ord)
157
158data PolygonMode
159 = PolygonPoint PointSize
160 | PolygonLine Float
161 | PolygonFill
162 deriving (Show, Eq, Ord)
163
164data ProvokingVertex
165 = FirstVertex
166 | LastVertex
167 deriving (Show, Eq, Ord)
168
169data CullMode
170 = CullNone
171 | CullFront FrontFace
172 | CullBack FrontFace
173 deriving (Show, Eq, Ord)
174
175data ComparisonFunction
176 = Never
177 | Less
178 | Equal
179 | Lequal
180 | Greater
181 | Notequal
182 | Gequal
183 | Always
184 deriving (Show, Eq, Ord)
185
186type DepthFunction = ComparisonFunction
187
188data StencilOperation
189 = OpZero
190 | OpKeep
191 | OpReplace
192 | OpIncr
193 | OpIncrWrap
194 | OpDecr
195 | OpDecrWrap
196 | OpInvert
197 deriving (Show, Eq, Ord)
198
199data BlendEquation
200 = FuncAdd
201 | FuncSubtract
202 | FuncReverseSubtract
203 | Min
204 | Max
205 deriving (Show, Eq, Ord)
206
207data BlendingFactor
208 = Zero
209 | One
210 | SrcColor
211 | OneMinusSrcColor
212 | DstColor
213 | OneMinusDstColor
214 | SrcAlpha
215 | OneMinusSrcAlpha
216 | DstAlpha
217 | OneMinusDstAlpha
218 | ConstantColor
219 | OneMinusConstantColor
220 | ConstantAlpha
221 | OneMinusConstantAlpha
222 | SrcAlphaSaturate
223 deriving (Show, Eq, Ord)
224
225data LogicOperation
226 = Clear
227 | And
228 | AndReverse
229 | Copy
230 | AndInverted
231 | Noop
232 | Xor
233 | Or
234 | Nor
235 | Equiv
236 | Invert
237 | OrReverse
238 | CopyInverted
239 | OrInverted
240 | Nand
241 | Set
242 deriving (Show, Eq, Ord)
243
244data StencilOps
245 = StencilOps
246 { frontStencilOp :: StencilOperation
247 , backStencilOp :: StencilOperation
248 }
249
250 deriving (Show, Eq, Ord)
251
252data StencilTest
253 = StencilTest
254 { stencilComparision :: ComparisonFunction
255 , stencilReference :: Int32
256 , stencilMask :: Word32
257 }
258
259 deriving (Show, Eq, Ord)
260
261data StencilTests
262 = StencilTests StencilTest StencilTest
263 deriving (Show, Eq, Ord)
264
265data FetchPrimitive
266 = Points
267 | Lines
268 | Triangles
269 | LinesAdjacency
270 | TrianglesAdjacency
271 deriving (Show, Eq, Ord)
272
273data OutputPrimitive
274 = TrianglesOutput
275 | LinesOutput
276 | PointsOutput
277 deriving (Show, Eq, Ord)
278
279data ColorArity
280 = Red
281 | RG
282 | RGB
283 | RGBA
284 deriving (Show, Eq, Ord)
285
286data Blending
287 = NoBlending
288 | BlendLogicOp LogicOperation
289 | Blend
290 { colorEqSrc :: BlendEquation
291 , alphaEqSrc :: BlendEquation
292 , colorFSrc :: BlendingFactor
293 , colorFDst :: BlendingFactor
294 , alphaFSrc :: BlendingFactor
295 , alphaFDst :: BlendingFactor
296 , color :: V4F
297 }
298
299 deriving (Show, Eq, Ord)
300
301data RasterContext
302 = PointCtx PointSize Float PointSpriteCoordOrigin
303 | LineCtx Float ProvokingVertex
304 | TriangleCtx CullMode PolygonMode PolygonOffset ProvokingVertex
305 deriving (Show, Eq, Ord)
306
307data FragmentOperation
308 = DepthOp DepthFunction Bool
309 | StencilOp StencilTests StencilOps StencilOps
310 | ColorOp Blending Value
311 deriving (Show, Eq, Ord)
312
313data AccumulationContext
314 = AccumulationContext
315 { accViewportName :: Maybe String
316 , accOperations :: [FragmentOperation]
317 }
318
319 deriving (Show, Eq, Ord)
320
321data TextureDataType
322 = FloatT ColorArity
323 | IntT ColorArity
324 | WordT ColorArity
325 | ShadowT
326 deriving (Show, Eq, Ord)
327
328data TextureType
329 = Texture1D TextureDataType Int
330 | Texture2D TextureDataType Int
331 | Texture3D TextureDataType
332 | TextureCube TextureDataType
333 | TextureRect TextureDataType
334 | Texture2DMS TextureDataType Int Int Bool
335 | TextureBuffer TextureDataType
336 deriving (Show, Eq, Ord)
337
338data MipMap
339 = Mip Int Int
340 | NoMip
341 | AutoMip Int Int
342 deriving (Show, Eq, Ord)
343
344data Filter
345 = Nearest
346 | Linear
347 | NearestMipmapNearest
348 | NearestMipmapLinear
349 | LinearMipmapNearest
350 | LinearMipmapLinear
351 deriving (Show, Eq, Ord)
352
353data EdgeMode
354 = Repeat
355 | MirroredRepeat
356 | ClampToEdge
357 | ClampToBorder
358 deriving (Show, Eq, Ord)
359
360data ImageSemantic
361 = Depth
362 | Stencil
363 | Color
364 deriving (Show, Eq, Ord)
365
366data ImageRef
367 = TextureImage TextureName Int (Maybe Int)
368 | Framebuffer ImageSemantic
369 deriving (Show, Eq, Ord)
370
371data ClearImage
372 = ClearImage
373 { imageSemantic :: ImageSemantic
374 , clearValue :: Value
375 }
376
377 deriving (Show, Eq, Ord)
378
379data Command
380 = SetRasterContext RasterContext
381 | SetAccumulationContext AccumulationContext
382 | SetRenderTarget RenderTargetName
383 | SetProgram ProgramName
384 | SetSamplerUniform UniformName TextureUnit
385 | SetTexture TextureUnit TextureName
386 | SetSampler TextureUnit (Maybe SamplerName)
387 | RenderSlot SlotName
388 | RenderStream StreamName
389 | ClearRenderTarget (Vector ClearImage)
390 | GenerateMipMap TextureUnit
391 | SaveImage FrameBufferComponent ImageRef
392 | LoadImage ImageRef FrameBufferComponent
393 deriving (Show, Eq, Ord)
394
395data SamplerDescriptor
396 = SamplerDescriptor
397 { samplerWrapS :: EdgeMode
398 , samplerWrapT :: Maybe EdgeMode
399 , samplerWrapR :: Maybe EdgeMode
400 , samplerMinFilter :: Filter
401 , samplerMagFilter :: Filter
402 , samplerBorderColor :: Value
403 , samplerMinLod :: Maybe Float
404 , samplerMaxLod :: Maybe Float
405 , samplerLodBias :: Float
406 , samplerCompareFunc :: Maybe ComparisonFunction
407 }
408
409 deriving (Show, Eq, Ord)
410
411data TextureDescriptor
412 = TextureDescriptor
413 { textureType :: TextureType
414 , textureSize :: Value
415 , textureSemantic :: ImageSemantic
416 , textureSampler :: SamplerDescriptor
417 , textureBaseLevel :: Int
418 , textureMaxLevel :: Int
419 }
420
421 deriving (Show, Eq, Ord)
422
423data Parameter
424 = Parameter
425 { name :: String
426 , ty :: InputType
427 }
428
429 deriving (Show, Eq, Ord)
430
431data Program
432 = Program
433 { programUniforms :: Map UniformName InputType
434 , programStreams :: Map UniformName Parameter
435 , programInTextures :: Map UniformName InputType
436 , programOutput :: Vector Parameter
437 , vertexShader :: String
438 , geometryShader :: Maybe String
439 , fragmentShader :: String
440 }
441
442 deriving (Show, Eq, Ord)
443
444data Slot
445 = Slot
446 { slotName :: String
447 , slotStreams :: Map String InputType
448 , slotUniforms :: Map UniformName InputType
449 , slotPrimitive :: FetchPrimitive
450 , slotPrograms :: Vector ProgramName
451 }
452
453 deriving (Show, Eq, Ord)
454
455data StreamData
456 = StreamData
457 { streamData :: Map String ArrayValue
458 , streamType :: Map String InputType
459 , streamPrimitive :: FetchPrimitive
460 , streamPrograms :: Vector ProgramName
461 }
462
463 deriving (Show, Eq, Ord)
464
465data TargetItem
466 = TargetItem
467 { targetSemantic :: ImageSemantic
468 , targetRef :: Maybe ImageRef
469 }
470
471 deriving (Show, Eq, Ord)
472
473data RenderTarget
474 = RenderTarget
475 { renderTargets :: Vector TargetItem
476 }
477
478 deriving (Show, Eq, Ord)
479
480data Backend
481 = WebGL1
482 | OpenGL33
483 deriving (Show, Eq, Ord)
484
485data Pipeline
486 = Pipeline
487 { backend :: Backend
488 , textures :: Vector TextureDescriptor
489 , samplers :: Vector SamplerDescriptor
490 , targets :: Vector RenderTarget
491 , programs :: Vector Program
492 , slots :: Vector Slot
493 , streams :: Vector StreamData
494 , commands :: Vector Command
495 }
496
497 deriving (Show, Eq, Ord)
498
499
500instance ToJSON ArrayValue where
501 toJSON v = case v of
502 VBoolArray arg0 -> object [ "tag" .= ("VBoolArray" :: Text), "arg0" .= arg0]
503 VIntArray arg0 -> object [ "tag" .= ("VIntArray" :: Text), "arg0" .= arg0]
504 VWordArray arg0 -> object [ "tag" .= ("VWordArray" :: Text), "arg0" .= arg0]
505 VFloatArray arg0 -> object [ "tag" .= ("VFloatArray" :: Text), "arg0" .= arg0]
506
507instance FromJSON ArrayValue where
508 parseJSON (Object obj) = do
509 tag <- obj .: "tag"
510 case tag :: Text of
511 "VBoolArray" -> VBoolArray <$> obj .: "arg0"
512 "VIntArray" -> VIntArray <$> obj .: "arg0"
513 "VWordArray" -> VWordArray <$> obj .: "arg0"
514 "VFloatArray" -> VFloatArray <$> obj .: "arg0"
515 parseJSON _ = mzero
516
517instance ToJSON Value where
518 toJSON v = case v of
519 VBool arg0 -> object [ "tag" .= ("VBool" :: Text), "arg0" .= arg0]
520 VV2B arg0 -> object [ "tag" .= ("VV2B" :: Text), "arg0" .= arg0]
521 VV3B arg0 -> object [ "tag" .= ("VV3B" :: Text), "arg0" .= arg0]
522 VV4B arg0 -> object [ "tag" .= ("VV4B" :: Text), "arg0" .= arg0]
523 VWord arg0 -> object [ "tag" .= ("VWord" :: Text), "arg0" .= arg0]
524 VV2U arg0 -> object [ "tag" .= ("VV2U" :: Text), "arg0" .= arg0]
525 VV3U arg0 -> object [ "tag" .= ("VV3U" :: Text), "arg0" .= arg0]
526 VV4U arg0 -> object [ "tag" .= ("VV4U" :: Text), "arg0" .= arg0]
527 VInt arg0 -> object [ "tag" .= ("VInt" :: Text), "arg0" .= arg0]
528 VV2I arg0 -> object [ "tag" .= ("VV2I" :: Text), "arg0" .= arg0]
529 VV3I arg0 -> object [ "tag" .= ("VV3I" :: Text), "arg0" .= arg0]
530 VV4I arg0 -> object [ "tag" .= ("VV4I" :: Text), "arg0" .= arg0]
531 VFloat arg0 -> object [ "tag" .= ("VFloat" :: Text), "arg0" .= arg0]
532 VV2F arg0 -> object [ "tag" .= ("VV2F" :: Text), "arg0" .= arg0]
533 VV3F arg0 -> object [ "tag" .= ("VV3F" :: Text), "arg0" .= arg0]
534 VV4F arg0 -> object [ "tag" .= ("VV4F" :: Text), "arg0" .= arg0]
535 VM22F arg0 -> object [ "tag" .= ("VM22F" :: Text), "arg0" .= arg0]
536 VM23F arg0 -> object [ "tag" .= ("VM23F" :: Text), "arg0" .= arg0]
537 VM24F arg0 -> object [ "tag" .= ("VM24F" :: Text), "arg0" .= arg0]
538 VM32F arg0 -> object [ "tag" .= ("VM32F" :: Text), "arg0" .= arg0]
539 VM33F arg0 -> object [ "tag" .= ("VM33F" :: Text), "arg0" .= arg0]
540 VM34F arg0 -> object [ "tag" .= ("VM34F" :: Text), "arg0" .= arg0]
541 VM42F arg0 -> object [ "tag" .= ("VM42F" :: Text), "arg0" .= arg0]
542 VM43F arg0 -> object [ "tag" .= ("VM43F" :: Text), "arg0" .= arg0]
543 VM44F arg0 -> object [ "tag" .= ("VM44F" :: Text), "arg0" .= arg0]
544
545instance FromJSON Value where
546 parseJSON (Object obj) = do
547 tag <- obj .: "tag"
548 case tag :: Text of
549 "VBool" -> VBool <$> obj .: "arg0"
550 "VV2B" -> VV2B <$> obj .: "arg0"
551 "VV3B" -> VV3B <$> obj .: "arg0"
552 "VV4B" -> VV4B <$> obj .: "arg0"
553 "VWord" -> VWord <$> obj .: "arg0"
554 "VV2U" -> VV2U <$> obj .: "arg0"
555 "VV3U" -> VV3U <$> obj .: "arg0"
556 "VV4U" -> VV4U <$> obj .: "arg0"
557 "VInt" -> VInt <$> obj .: "arg0"
558 "VV2I" -> VV2I <$> obj .: "arg0"
559 "VV3I" -> VV3I <$> obj .: "arg0"
560 "VV4I" -> VV4I <$> obj .: "arg0"
561 "VFloat" -> VFloat <$> obj .: "arg0"
562 "VV2F" -> VV2F <$> obj .: "arg0"
563 "VV3F" -> VV3F <$> obj .: "arg0"
564 "VV4F" -> VV4F <$> obj .: "arg0"
565 "VM22F" -> VM22F <$> obj .: "arg0"
566 "VM23F" -> VM23F <$> obj .: "arg0"
567 "VM24F" -> VM24F <$> obj .: "arg0"
568 "VM32F" -> VM32F <$> obj .: "arg0"
569 "VM33F" -> VM33F <$> obj .: "arg0"
570 "VM34F" -> VM34F <$> obj .: "arg0"
571 "VM42F" -> VM42F <$> obj .: "arg0"
572 "VM43F" -> VM43F <$> obj .: "arg0"
573 "VM44F" -> VM44F <$> obj .: "arg0"
574 parseJSON _ = mzero
575
576instance ToJSON InputType where
577 toJSON v = case v of
578 Bool -> object [ "tag" .= ("Bool" :: Text)]
579 V2B -> object [ "tag" .= ("V2B" :: Text)]
580 V3B -> object [ "tag" .= ("V3B" :: Text)]
581 V4B -> object [ "tag" .= ("V4B" :: Text)]
582 Word -> object [ "tag" .= ("Word" :: Text)]
583 V2U -> object [ "tag" .= ("V2U" :: Text)]
584 V3U -> object [ "tag" .= ("V3U" :: Text)]
585 V4U -> object [ "tag" .= ("V4U" :: Text)]
586 Int -> object [ "tag" .= ("Int" :: Text)]
587 V2I -> object [ "tag" .= ("V2I" :: Text)]
588 V3I -> object [ "tag" .= ("V3I" :: Text)]
589 V4I -> object [ "tag" .= ("V4I" :: Text)]
590 Float -> object [ "tag" .= ("Float" :: Text)]
591 V2F -> object [ "tag" .= ("V2F" :: Text)]
592 V3F -> object [ "tag" .= ("V3F" :: Text)]
593 V4F -> object [ "tag" .= ("V4F" :: Text)]
594 M22F -> object [ "tag" .= ("M22F" :: Text)]
595 M23F -> object [ "tag" .= ("M23F" :: Text)]
596 M24F -> object [ "tag" .= ("M24F" :: Text)]
597 M32F -> object [ "tag" .= ("M32F" :: Text)]
598 M33F -> object [ "tag" .= ("M33F" :: Text)]
599 M34F -> object [ "tag" .= ("M34F" :: Text)]
600 M42F -> object [ "tag" .= ("M42F" :: Text)]
601 M43F -> object [ "tag" .= ("M43F" :: Text)]
602 M44F -> object [ "tag" .= ("M44F" :: Text)]
603 STexture1D -> object [ "tag" .= ("STexture1D" :: Text)]
604 STexture2D -> object [ "tag" .= ("STexture2D" :: Text)]
605 STextureCube -> object [ "tag" .= ("STextureCube" :: Text)]
606 STexture1DArray -> object [ "tag" .= ("STexture1DArray" :: Text)]
607 STexture2DArray -> object [ "tag" .= ("STexture2DArray" :: Text)]
608 STexture2DRect -> object [ "tag" .= ("STexture2DRect" :: Text)]
609 FTexture1D -> object [ "tag" .= ("FTexture1D" :: Text)]
610 FTexture2D -> object [ "tag" .= ("FTexture2D" :: Text)]
611 FTexture3D -> object [ "tag" .= ("FTexture3D" :: Text)]
612 FTextureCube -> object [ "tag" .= ("FTextureCube" :: Text)]
613 FTexture1DArray -> object [ "tag" .= ("FTexture1DArray" :: Text)]
614 FTexture2DArray -> object [ "tag" .= ("FTexture2DArray" :: Text)]
615 FTexture2DMS -> object [ "tag" .= ("FTexture2DMS" :: Text)]
616 FTexture2DMSArray -> object [ "tag" .= ("FTexture2DMSArray" :: Text)]
617 FTextureBuffer -> object [ "tag" .= ("FTextureBuffer" :: Text)]
618 FTexture2DRect -> object [ "tag" .= ("FTexture2DRect" :: Text)]
619 ITexture1D -> object [ "tag" .= ("ITexture1D" :: Text)]
620 ITexture2D -> object [ "tag" .= ("ITexture2D" :: Text)]
621 ITexture3D -> object [ "tag" .= ("ITexture3D" :: Text)]
622 ITextureCube -> object [ "tag" .= ("ITextureCube" :: Text)]
623 ITexture1DArray -> object [ "tag" .= ("ITexture1DArray" :: Text)]
624 ITexture2DArray -> object [ "tag" .= ("ITexture2DArray" :: Text)]
625 ITexture2DMS -> object [ "tag" .= ("ITexture2DMS" :: Text)]
626 ITexture2DMSArray -> object [ "tag" .= ("ITexture2DMSArray" :: Text)]
627 ITextureBuffer -> object [ "tag" .= ("ITextureBuffer" :: Text)]
628 ITexture2DRect -> object [ "tag" .= ("ITexture2DRect" :: Text)]
629 UTexture1D -> object [ "tag" .= ("UTexture1D" :: Text)]
630 UTexture2D -> object [ "tag" .= ("UTexture2D" :: Text)]
631 UTexture3D -> object [ "tag" .= ("UTexture3D" :: Text)]
632 UTextureCube -> object [ "tag" .= ("UTextureCube" :: Text)]
633 UTexture1DArray -> object [ "tag" .= ("UTexture1DArray" :: Text)]
634 UTexture2DArray -> object [ "tag" .= ("UTexture2DArray" :: Text)]
635 UTexture2DMS -> object [ "tag" .= ("UTexture2DMS" :: Text)]
636 UTexture2DMSArray -> object [ "tag" .= ("UTexture2DMSArray" :: Text)]
637 UTextureBuffer -> object [ "tag" .= ("UTextureBuffer" :: Text)]
638 UTexture2DRect -> object [ "tag" .= ("UTexture2DRect" :: Text)]
639
640instance FromJSON InputType where
641 parseJSON (Object obj) = do
642 tag <- obj .: "tag"
643 case tag :: Text of
644 "Bool" -> pure Bool
645 "V2B" -> pure V2B
646 "V3B" -> pure V3B
647 "V4B" -> pure V4B
648 "Word" -> pure Word
649 "V2U" -> pure V2U
650 "V3U" -> pure V3U
651 "V4U" -> pure V4U
652 "Int" -> pure Int
653 "V2I" -> pure V2I
654 "V3I" -> pure V3I
655 "V4I" -> pure V4I
656 "Float" -> pure Float
657 "V2F" -> pure V2F
658 "V3F" -> pure V3F
659 "V4F" -> pure V4F
660 "M22F" -> pure M22F
661 "M23F" -> pure M23F
662 "M24F" -> pure M24F
663 "M32F" -> pure M32F
664 "M33F" -> pure M33F
665 "M34F" -> pure M34F
666 "M42F" -> pure M42F
667 "M43F" -> pure M43F
668 "M44F" -> pure M44F
669 "STexture1D" -> pure STexture1D
670 "STexture2D" -> pure STexture2D
671 "STextureCube" -> pure STextureCube
672 "STexture1DArray" -> pure STexture1DArray
673 "STexture2DArray" -> pure STexture2DArray
674 "STexture2DRect" -> pure STexture2DRect
675 "FTexture1D" -> pure FTexture1D
676 "FTexture2D" -> pure FTexture2D
677 "FTexture3D" -> pure FTexture3D
678 "FTextureCube" -> pure FTextureCube
679 "FTexture1DArray" -> pure FTexture1DArray
680 "FTexture2DArray" -> pure FTexture2DArray
681 "FTexture2DMS" -> pure FTexture2DMS
682 "FTexture2DMSArray" -> pure FTexture2DMSArray
683 "FTextureBuffer" -> pure FTextureBuffer
684 "FTexture2DRect" -> pure FTexture2DRect
685 "ITexture1D" -> pure ITexture1D
686 "ITexture2D" -> pure ITexture2D
687 "ITexture3D" -> pure ITexture3D
688 "ITextureCube" -> pure ITextureCube
689 "ITexture1DArray" -> pure ITexture1DArray
690 "ITexture2DArray" -> pure ITexture2DArray
691 "ITexture2DMS" -> pure ITexture2DMS
692 "ITexture2DMSArray" -> pure ITexture2DMSArray
693 "ITextureBuffer" -> pure ITextureBuffer
694 "ITexture2DRect" -> pure ITexture2DRect
695 "UTexture1D" -> pure UTexture1D
696 "UTexture2D" -> pure UTexture2D
697 "UTexture3D" -> pure UTexture3D
698 "UTextureCube" -> pure UTextureCube
699 "UTexture1DArray" -> pure UTexture1DArray
700 "UTexture2DArray" -> pure UTexture2DArray
701 "UTexture2DMS" -> pure UTexture2DMS
702 "UTexture2DMSArray" -> pure UTexture2DMSArray
703 "UTextureBuffer" -> pure UTextureBuffer
704 "UTexture2DRect" -> pure UTexture2DRect
705 parseJSON _ = mzero
706
707instance ToJSON PointSpriteCoordOrigin where
708 toJSON v = case v of
709 LowerLeft -> object [ "tag" .= ("LowerLeft" :: Text)]
710 UpperLeft -> object [ "tag" .= ("UpperLeft" :: Text)]
711
712instance FromJSON PointSpriteCoordOrigin where
713 parseJSON (Object obj) = do
714 tag <- obj .: "tag"
715 case tag :: Text of
716 "LowerLeft" -> pure LowerLeft
717 "UpperLeft" -> pure UpperLeft
718 parseJSON _ = mzero
719
720instance ToJSON PointSize where
721 toJSON v = case v of
722 PointSize arg0 -> object [ "tag" .= ("PointSize" :: Text), "arg0" .= arg0]
723 ProgramPointSize -> object [ "tag" .= ("ProgramPointSize" :: Text)]
724
725instance FromJSON PointSize where
726 parseJSON (Object obj) = do
727 tag <- obj .: "tag"
728 case tag :: Text of
729 "PointSize" -> PointSize <$> obj .: "arg0"
730 "ProgramPointSize" -> pure ProgramPointSize
731 parseJSON _ = mzero
732
733instance ToJSON PolygonOffset where
734 toJSON v = case v of
735 NoOffset -> object [ "tag" .= ("NoOffset" :: Text)]
736 Offset arg0 arg1 -> object [ "tag" .= ("Offset" :: Text), "arg0" .= arg0, "arg1" .= arg1]
737
738instance FromJSON PolygonOffset where
739 parseJSON (Object obj) = do
740 tag <- obj .: "tag"
741 case tag :: Text of
742 "NoOffset" -> pure NoOffset
743 "Offset" -> Offset <$> obj .: "arg0" <*> obj .: "arg1"
744 parseJSON _ = mzero
745
746instance ToJSON FrontFace where
747 toJSON v = case v of
748 CCW -> object [ "tag" .= ("CCW" :: Text)]
749 CW -> object [ "tag" .= ("CW" :: Text)]
750
751instance FromJSON FrontFace where
752 parseJSON (Object obj) = do
753 tag <- obj .: "tag"
754 case tag :: Text of
755 "CCW" -> pure CCW
756 "CW" -> pure CW
757 parseJSON _ = mzero
758
759instance ToJSON PolygonMode where
760 toJSON v = case v of
761 PolygonPoint arg0 -> object [ "tag" .= ("PolygonPoint" :: Text), "arg0" .= arg0]
762 PolygonLine arg0 -> object [ "tag" .= ("PolygonLine" :: Text), "arg0" .= arg0]
763 PolygonFill -> object [ "tag" .= ("PolygonFill" :: Text)]
764
765instance FromJSON PolygonMode where
766 parseJSON (Object obj) = do
767 tag <- obj .: "tag"
768 case tag :: Text of
769 "PolygonPoint" -> PolygonPoint <$> obj .: "arg0"
770 "PolygonLine" -> PolygonLine <$> obj .: "arg0"
771 "PolygonFill" -> pure PolygonFill
772 parseJSON _ = mzero
773
774instance ToJSON ProvokingVertex where
775 toJSON v = case v of
776 FirstVertex -> object [ "tag" .= ("FirstVertex" :: Text)]
777 LastVertex -> object [ "tag" .= ("LastVertex" :: Text)]
778
779instance FromJSON ProvokingVertex where
780 parseJSON (Object obj) = do
781 tag <- obj .: "tag"
782 case tag :: Text of
783 "FirstVertex" -> pure FirstVertex
784 "LastVertex" -> pure LastVertex
785 parseJSON _ = mzero
786
787instance ToJSON CullMode where
788 toJSON v = case v of
789 CullNone -> object [ "tag" .= ("CullNone" :: Text)]
790 CullFront arg0 -> object [ "tag" .= ("CullFront" :: Text), "arg0" .= arg0]
791 CullBack arg0 -> object [ "tag" .= ("CullBack" :: Text), "arg0" .= arg0]
792
793instance FromJSON CullMode where
794 parseJSON (Object obj) = do
795 tag <- obj .: "tag"
796 case tag :: Text of
797 "CullNone" -> pure CullNone
798 "CullFront" -> CullFront <$> obj .: "arg0"
799 "CullBack" -> CullBack <$> obj .: "arg0"
800 parseJSON _ = mzero
801
802instance ToJSON ComparisonFunction where
803 toJSON v = case v of
804 Never -> object [ "tag" .= ("Never" :: Text)]
805 Less -> object [ "tag" .= ("Less" :: Text)]
806 Equal -> object [ "tag" .= ("Equal" :: Text)]
807 Lequal -> object [ "tag" .= ("Lequal" :: Text)]
808 Greater -> object [ "tag" .= ("Greater" :: Text)]
809 Notequal -> object [ "tag" .= ("Notequal" :: Text)]
810 Gequal -> object [ "tag" .= ("Gequal" :: Text)]
811 Always -> object [ "tag" .= ("Always" :: Text)]
812
813instance FromJSON ComparisonFunction where
814 parseJSON (Object obj) = do
815 tag <- obj .: "tag"
816 case tag :: Text of
817 "Never" -> pure Never
818 "Less" -> pure Less
819 "Equal" -> pure Equal
820 "Lequal" -> pure Lequal
821 "Greater" -> pure Greater
822 "Notequal" -> pure Notequal
823 "Gequal" -> pure Gequal
824 "Always" -> pure Always
825 parseJSON _ = mzero
826
827instance ToJSON StencilOperation where
828 toJSON v = case v of
829 OpZero -> object [ "tag" .= ("OpZero" :: Text)]
830 OpKeep -> object [ "tag" .= ("OpKeep" :: Text)]
831 OpReplace -> object [ "tag" .= ("OpReplace" :: Text)]
832 OpIncr -> object [ "tag" .= ("OpIncr" :: Text)]
833 OpIncrWrap -> object [ "tag" .= ("OpIncrWrap" :: Text)]
834 OpDecr -> object [ "tag" .= ("OpDecr" :: Text)]
835 OpDecrWrap -> object [ "tag" .= ("OpDecrWrap" :: Text)]
836 OpInvert -> object [ "tag" .= ("OpInvert" :: Text)]
837
838instance FromJSON StencilOperation where
839 parseJSON (Object obj) = do
840 tag <- obj .: "tag"
841 case tag :: Text of
842 "OpZero" -> pure OpZero
843 "OpKeep" -> pure OpKeep
844 "OpReplace" -> pure OpReplace
845 "OpIncr" -> pure OpIncr
846 "OpIncrWrap" -> pure OpIncrWrap
847 "OpDecr" -> pure OpDecr
848 "OpDecrWrap" -> pure OpDecrWrap
849 "OpInvert" -> pure OpInvert
850 parseJSON _ = mzero
851
852instance ToJSON BlendEquation where
853 toJSON v = case v of
854 FuncAdd -> object [ "tag" .= ("FuncAdd" :: Text)]
855 FuncSubtract -> object [ "tag" .= ("FuncSubtract" :: Text)]
856 FuncReverseSubtract -> object [ "tag" .= ("FuncReverseSubtract" :: Text)]
857 Min -> object [ "tag" .= ("Min" :: Text)]
858 Max -> object [ "tag" .= ("Max" :: Text)]
859
860instance FromJSON BlendEquation where
861 parseJSON (Object obj) = do
862 tag <- obj .: "tag"
863 case tag :: Text of
864 "FuncAdd" -> pure FuncAdd
865 "FuncSubtract" -> pure FuncSubtract
866 "FuncReverseSubtract" -> pure FuncReverseSubtract
867 "Min" -> pure Min
868 "Max" -> pure Max
869 parseJSON _ = mzero
870
871instance ToJSON BlendingFactor where
872 toJSON v = case v of
873 Zero -> object [ "tag" .= ("Zero" :: Text)]
874 One -> object [ "tag" .= ("One" :: Text)]
875 SrcColor -> object [ "tag" .= ("SrcColor" :: Text)]
876 OneMinusSrcColor -> object [ "tag" .= ("OneMinusSrcColor" :: Text)]
877 DstColor -> object [ "tag" .= ("DstColor" :: Text)]
878 OneMinusDstColor -> object [ "tag" .= ("OneMinusDstColor" :: Text)]
879 SrcAlpha -> object [ "tag" .= ("SrcAlpha" :: Text)]
880 OneMinusSrcAlpha -> object [ "tag" .= ("OneMinusSrcAlpha" :: Text)]
881 DstAlpha -> object [ "tag" .= ("DstAlpha" :: Text)]
882 OneMinusDstAlpha -> object [ "tag" .= ("OneMinusDstAlpha" :: Text)]
883 ConstantColor -> object [ "tag" .= ("ConstantColor" :: Text)]
884 OneMinusConstantColor -> object [ "tag" .= ("OneMinusConstantColor" :: Text)]
885 ConstantAlpha -> object [ "tag" .= ("ConstantAlpha" :: Text)]
886 OneMinusConstantAlpha -> object [ "tag" .= ("OneMinusConstantAlpha" :: Text)]
887 SrcAlphaSaturate -> object [ "tag" .= ("SrcAlphaSaturate" :: Text)]
888
889instance FromJSON BlendingFactor where
890 parseJSON (Object obj) = do
891 tag <- obj .: "tag"
892 case tag :: Text of
893 "Zero" -> pure Zero
894 "One" -> pure One
895 "SrcColor" -> pure SrcColor
896 "OneMinusSrcColor" -> pure OneMinusSrcColor
897 "DstColor" -> pure DstColor
898 "OneMinusDstColor" -> pure OneMinusDstColor
899 "SrcAlpha" -> pure SrcAlpha
900 "OneMinusSrcAlpha" -> pure OneMinusSrcAlpha
901 "DstAlpha" -> pure DstAlpha
902 "OneMinusDstAlpha" -> pure OneMinusDstAlpha
903 "ConstantColor" -> pure ConstantColor
904 "OneMinusConstantColor" -> pure OneMinusConstantColor
905 "ConstantAlpha" -> pure ConstantAlpha
906 "OneMinusConstantAlpha" -> pure OneMinusConstantAlpha
907 "SrcAlphaSaturate" -> pure SrcAlphaSaturate
908 parseJSON _ = mzero
909
910instance ToJSON LogicOperation where
911 toJSON v = case v of
912 Clear -> object [ "tag" .= ("Clear" :: Text)]
913 And -> object [ "tag" .= ("And" :: Text)]
914 AndReverse -> object [ "tag" .= ("AndReverse" :: Text)]
915 Copy -> object [ "tag" .= ("Copy" :: Text)]
916 AndInverted -> object [ "tag" .= ("AndInverted" :: Text)]
917 Noop -> object [ "tag" .= ("Noop" :: Text)]
918 Xor -> object [ "tag" .= ("Xor" :: Text)]
919 Or -> object [ "tag" .= ("Or" :: Text)]
920 Nor -> object [ "tag" .= ("Nor" :: Text)]
921 Equiv -> object [ "tag" .= ("Equiv" :: Text)]
922 Invert -> object [ "tag" .= ("Invert" :: Text)]
923 OrReverse -> object [ "tag" .= ("OrReverse" :: Text)]
924 CopyInverted -> object [ "tag" .= ("CopyInverted" :: Text)]
925 OrInverted -> object [ "tag" .= ("OrInverted" :: Text)]
926 Nand -> object [ "tag" .= ("Nand" :: Text)]
927 Set -> object [ "tag" .= ("Set" :: Text)]
928
929instance FromJSON LogicOperation where
930 parseJSON (Object obj) = do
931 tag <- obj .: "tag"
932 case tag :: Text 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 parseJSON _ = mzero
950
951instance ToJSON StencilOps where
952 toJSON v = case v of
953 StencilOps{..} -> object
954 [ "tag" .= ("StencilOps" :: Text)
955 , "frontStencilOp" .= frontStencilOp
956 , "backStencilOp" .= backStencilOp
957 ]
958
959instance FromJSON StencilOps where
960 parseJSON (Object obj) = do
961 tag <- obj .: "tag"
962 case tag :: Text of
963 "StencilOps" -> do
964 frontStencilOp <- obj .: "frontStencilOp"
965 backStencilOp <- obj .: "backStencilOp"
966 pure $ StencilOps
967 { frontStencilOp = frontStencilOp
968 , backStencilOp = backStencilOp
969 }
970 parseJSON _ = mzero
971
972instance ToJSON StencilTest where
973 toJSON v = case v of
974 StencilTest{..} -> object
975 [ "tag" .= ("StencilTest" :: Text)
976 , "stencilComparision" .= stencilComparision
977 , "stencilReference" .= stencilReference
978 , "stencilMask" .= stencilMask
979 ]
980
981instance FromJSON StencilTest where
982 parseJSON (Object obj) = do
983 tag <- obj .: "tag"
984 case tag :: Text of
985 "StencilTest" -> do
986 stencilComparision <- obj .: "stencilComparision"
987 stencilReference <- obj .: "stencilReference"
988 stencilMask <- obj .: "stencilMask"
989 pure $ StencilTest
990 { stencilComparision = stencilComparision
991 , stencilReference = stencilReference
992 , stencilMask = stencilMask
993 }
994 parseJSON _ = mzero
995
996instance ToJSON StencilTests where
997 toJSON v = case v of
998 StencilTests arg0 arg1 -> object [ "tag" .= ("StencilTests" :: Text), "arg0" .= arg0, "arg1" .= arg1]
999
1000instance FromJSON StencilTests where
1001 parseJSON (Object obj) = do
1002 tag <- obj .: "tag"
1003 case tag :: Text of
1004 "StencilTests" -> StencilTests <$> obj .: "arg0" <*> obj .: "arg1"
1005 parseJSON _ = mzero
1006
1007instance ToJSON FetchPrimitive where
1008 toJSON v = case v of
1009 Points -> object [ "tag" .= ("Points" :: Text)]
1010 Lines -> object [ "tag" .= ("Lines" :: Text)]
1011 Triangles -> object [ "tag" .= ("Triangles" :: Text)]
1012 LinesAdjacency -> object [ "tag" .= ("LinesAdjacency" :: Text)]
1013 TrianglesAdjacency -> object [ "tag" .= ("TrianglesAdjacency" :: Text)]
1014
1015instance FromJSON FetchPrimitive where
1016 parseJSON (Object obj) = do
1017 tag <- obj .: "tag"
1018 case tag :: Text of
1019 "Points" -> pure Points
1020 "Lines" -> pure Lines
1021 "Triangles" -> pure Triangles
1022 "LinesAdjacency" -> pure LinesAdjacency
1023 "TrianglesAdjacency" -> pure TrianglesAdjacency
1024 parseJSON _ = mzero
1025
1026instance ToJSON OutputPrimitive where
1027 toJSON v = case v of
1028 TrianglesOutput -> object [ "tag" .= ("TrianglesOutput" :: Text)]
1029 LinesOutput -> object [ "tag" .= ("LinesOutput" :: Text)]
1030 PointsOutput -> object [ "tag" .= ("PointsOutput" :: Text)]
1031
1032instance FromJSON OutputPrimitive where
1033 parseJSON (Object obj) = do
1034 tag <- obj .: "tag"
1035 case tag :: Text of
1036 "TrianglesOutput" -> pure TrianglesOutput
1037 "LinesOutput" -> pure LinesOutput
1038 "PointsOutput" -> pure PointsOutput
1039 parseJSON _ = mzero
1040
1041instance ToJSON ColorArity where
1042 toJSON v = case v of
1043 Red -> object [ "tag" .= ("Red" :: Text)]
1044 RG -> object [ "tag" .= ("RG" :: Text)]
1045 RGB -> object [ "tag" .= ("RGB" :: Text)]
1046 RGBA -> object [ "tag" .= ("RGBA" :: Text)]
1047
1048instance FromJSON ColorArity where
1049 parseJSON (Object obj) = do
1050 tag <- obj .: "tag"
1051 case tag :: Text of
1052 "Red" -> pure Red
1053 "RG" -> pure RG
1054 "RGB" -> pure RGB
1055 "RGBA" -> pure RGBA
1056 parseJSON _ = mzero
1057
1058instance ToJSON Blending where
1059 toJSON v = case v of
1060 NoBlending -> object [ "tag" .= ("NoBlending" :: Text)]
1061 BlendLogicOp arg0 -> object [ "tag" .= ("BlendLogicOp" :: Text), "arg0" .= arg0]
1062 Blend{..} -> object
1063 [ "tag" .= ("Blend" :: Text)
1064 , "colorEqSrc" .= colorEqSrc
1065 , "alphaEqSrc" .= alphaEqSrc
1066 , "colorFSrc" .= colorFSrc
1067 , "colorFDst" .= colorFDst
1068 , "alphaFSrc" .= alphaFSrc
1069 , "alphaFDst" .= alphaFDst
1070 , "color" .= color
1071 ]
1072
1073instance FromJSON Blending where
1074 parseJSON (Object obj) = do
1075 tag <- obj .: "tag"
1076 case tag :: Text of
1077 "NoBlending" -> pure NoBlending
1078 "BlendLogicOp" -> BlendLogicOp <$> obj .: "arg0"
1079 "Blend" -> do
1080 colorEqSrc <- obj .: "colorEqSrc"
1081 alphaEqSrc <- obj .: "alphaEqSrc"
1082 colorFSrc <- obj .: "colorFSrc"
1083 colorFDst <- obj .: "colorFDst"
1084 alphaFSrc <- obj .: "alphaFSrc"
1085 alphaFDst <- obj .: "alphaFDst"
1086 color <- obj .: "color"
1087 pure $ Blend
1088 { colorEqSrc = colorEqSrc
1089 , alphaEqSrc = alphaEqSrc
1090 , colorFSrc = colorFSrc
1091 , colorFDst = colorFDst
1092 , alphaFSrc = alphaFSrc
1093 , alphaFDst = alphaFDst
1094 , color = color
1095 }
1096 parseJSON _ = mzero
1097
1098instance ToJSON RasterContext where
1099 toJSON v = case v of
1100 PointCtx arg0 arg1 arg2 -> object [ "tag" .= ("PointCtx" :: Text), "arg0" .= arg0, "arg1" .= arg1, "arg2" .= arg2]
1101 LineCtx arg0 arg1 -> object [ "tag" .= ("LineCtx" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1102 TriangleCtx arg0 arg1 arg2 arg3 -> object [ "tag" .= ("TriangleCtx" :: Text), "arg0" .= arg0, "arg1" .= arg1, "arg2" .= arg2, "arg3" .= arg3]
1103
1104instance FromJSON RasterContext where
1105 parseJSON (Object obj) = do
1106 tag <- obj .: "tag"
1107 case tag :: Text of
1108 "PointCtx" -> PointCtx <$> obj .: "arg0" <*> obj .: "arg1" <*> obj .: "arg2"
1109 "LineCtx" -> LineCtx <$> obj .: "arg0" <*> obj .: "arg1"
1110 "TriangleCtx" -> TriangleCtx <$> obj .: "arg0" <*> obj .: "arg1" <*> obj .: "arg2" <*> obj .: "arg3"
1111 parseJSON _ = mzero
1112
1113instance ToJSON FragmentOperation where
1114 toJSON v = case v of
1115 DepthOp arg0 arg1 -> object [ "tag" .= ("DepthOp" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1116 StencilOp arg0 arg1 arg2 -> object [ "tag" .= ("StencilOp" :: Text), "arg0" .= arg0, "arg1" .= arg1, "arg2" .= arg2]
1117 ColorOp arg0 arg1 -> object [ "tag" .= ("ColorOp" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1118
1119instance FromJSON FragmentOperation where
1120 parseJSON (Object obj) = do
1121 tag <- obj .: "tag"
1122 case tag :: Text of
1123 "DepthOp" -> DepthOp <$> obj .: "arg0" <*> obj .: "arg1"
1124 "StencilOp" -> StencilOp <$> obj .: "arg0" <*> obj .: "arg1" <*> obj .: "arg2"
1125 "ColorOp" -> ColorOp <$> obj .: "arg0" <*> obj .: "arg1"
1126 parseJSON _ = mzero
1127
1128instance ToJSON AccumulationContext where
1129 toJSON v = case v of
1130 AccumulationContext{..} -> object
1131 [ "tag" .= ("AccumulationContext" :: Text)
1132 , "accViewportName" .= accViewportName
1133 , "accOperations" .= accOperations
1134 ]
1135
1136instance FromJSON AccumulationContext where
1137 parseJSON (Object obj) = do
1138 tag <- obj .: "tag"
1139 case tag :: Text of
1140 "AccumulationContext" -> do
1141 accViewportName <- obj .: "accViewportName"
1142 accOperations <- obj .: "accOperations"
1143 pure $ AccumulationContext
1144 { accViewportName = accViewportName
1145 , accOperations = accOperations
1146 }
1147 parseJSON _ = mzero
1148
1149instance ToJSON TextureDataType where
1150 toJSON v = case v of
1151 FloatT arg0 -> object [ "tag" .= ("FloatT" :: Text), "arg0" .= arg0]
1152 IntT arg0 -> object [ "tag" .= ("IntT" :: Text), "arg0" .= arg0]
1153 WordT arg0 -> object [ "tag" .= ("WordT" :: Text), "arg0" .= arg0]
1154 ShadowT -> object [ "tag" .= ("ShadowT" :: Text)]
1155
1156instance FromJSON TextureDataType where
1157 parseJSON (Object obj) = do
1158 tag <- obj .: "tag"
1159 case tag :: Text of
1160 "FloatT" -> FloatT <$> obj .: "arg0"
1161 "IntT" -> IntT <$> obj .: "arg0"
1162 "WordT" -> WordT <$> obj .: "arg0"
1163 "ShadowT" -> pure ShadowT
1164 parseJSON _ = mzero
1165
1166instance ToJSON TextureType where
1167 toJSON v = case v of
1168 Texture1D arg0 arg1 -> object [ "tag" .= ("Texture1D" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1169 Texture2D arg0 arg1 -> object [ "tag" .= ("Texture2D" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1170 Texture3D arg0 -> object [ "tag" .= ("Texture3D" :: Text), "arg0" .= arg0]
1171 TextureCube arg0 -> object [ "tag" .= ("TextureCube" :: Text), "arg0" .= arg0]
1172 TextureRect arg0 -> object [ "tag" .= ("TextureRect" :: Text), "arg0" .= arg0]
1173 Texture2DMS arg0 arg1 arg2 arg3 -> object [ "tag" .= ("Texture2DMS" :: Text), "arg0" .= arg0, "arg1" .= arg1, "arg2" .= arg2, "arg3" .= arg3]
1174 TextureBuffer arg0 -> object [ "tag" .= ("TextureBuffer" :: Text), "arg0" .= arg0]
1175
1176instance FromJSON TextureType where
1177 parseJSON (Object obj) = do
1178 tag <- obj .: "tag"
1179 case tag :: Text of
1180 "Texture1D" -> Texture1D <$> obj .: "arg0" <*> obj .: "arg1"
1181 "Texture2D" -> Texture2D <$> obj .: "arg0" <*> obj .: "arg1"
1182 "Texture3D" -> Texture3D <$> obj .: "arg0"
1183 "TextureCube" -> TextureCube <$> obj .: "arg0"
1184 "TextureRect" -> TextureRect <$> obj .: "arg0"
1185 "Texture2DMS" -> Texture2DMS <$> obj .: "arg0" <*> obj .: "arg1" <*> obj .: "arg2" <*> obj .: "arg3"
1186 "TextureBuffer" -> TextureBuffer <$> obj .: "arg0"
1187 parseJSON _ = mzero
1188
1189instance ToJSON MipMap where
1190 toJSON v = case v of
1191 Mip arg0 arg1 -> object [ "tag" .= ("Mip" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1192 NoMip -> object [ "tag" .= ("NoMip" :: Text)]
1193 AutoMip arg0 arg1 -> object [ "tag" .= ("AutoMip" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1194
1195instance FromJSON MipMap where
1196 parseJSON (Object obj) = do
1197 tag <- obj .: "tag"
1198 case tag :: Text of
1199 "Mip" -> Mip <$> obj .: "arg0" <*> obj .: "arg1"
1200 "NoMip" -> pure NoMip
1201 "AutoMip" -> AutoMip <$> obj .: "arg0" <*> obj .: "arg1"
1202 parseJSON _ = mzero
1203
1204instance ToJSON Filter where
1205 toJSON v = case v of
1206 Nearest -> object [ "tag" .= ("Nearest" :: Text)]
1207 Linear -> object [ "tag" .= ("Linear" :: Text)]
1208 NearestMipmapNearest -> object [ "tag" .= ("NearestMipmapNearest" :: Text)]
1209 NearestMipmapLinear -> object [ "tag" .= ("NearestMipmapLinear" :: Text)]
1210 LinearMipmapNearest -> object [ "tag" .= ("LinearMipmapNearest" :: Text)]
1211 LinearMipmapLinear -> object [ "tag" .= ("LinearMipmapLinear" :: Text)]
1212
1213instance FromJSON Filter where
1214 parseJSON (Object obj) = do
1215 tag <- obj .: "tag"
1216 case tag :: Text of
1217 "Nearest" -> pure Nearest
1218 "Linear" -> pure Linear
1219 "NearestMipmapNearest" -> pure NearestMipmapNearest
1220 "NearestMipmapLinear" -> pure NearestMipmapLinear
1221 "LinearMipmapNearest" -> pure LinearMipmapNearest
1222 "LinearMipmapLinear" -> pure LinearMipmapLinear
1223 parseJSON _ = mzero
1224
1225instance ToJSON EdgeMode where
1226 toJSON v = case v of
1227 Repeat -> object [ "tag" .= ("Repeat" :: Text)]
1228 MirroredRepeat -> object [ "tag" .= ("MirroredRepeat" :: Text)]
1229 ClampToEdge -> object [ "tag" .= ("ClampToEdge" :: Text)]
1230 ClampToBorder -> object [ "tag" .= ("ClampToBorder" :: Text)]
1231
1232instance FromJSON EdgeMode where
1233 parseJSON (Object obj) = do
1234 tag <- obj .: "tag"
1235 case tag :: Text of
1236 "Repeat" -> pure Repeat
1237 "MirroredRepeat" -> pure MirroredRepeat
1238 "ClampToEdge" -> pure ClampToEdge
1239 "ClampToBorder" -> pure ClampToBorder
1240 parseJSON _ = mzero
1241
1242instance ToJSON ImageSemantic where
1243 toJSON v = case v of
1244 Depth -> object [ "tag" .= ("Depth" :: Text)]
1245 Stencil -> object [ "tag" .= ("Stencil" :: Text)]
1246 Color -> object [ "tag" .= ("Color" :: Text)]
1247
1248instance FromJSON ImageSemantic where
1249 parseJSON (Object obj) = do
1250 tag <- obj .: "tag"
1251 case tag :: Text of
1252 "Depth" -> pure Depth
1253 "Stencil" -> pure Stencil
1254 "Color" -> pure Color
1255 parseJSON _ = mzero
1256
1257instance ToJSON ImageRef where
1258 toJSON v = case v of
1259 TextureImage arg0 arg1 arg2 -> object [ "tag" .= ("TextureImage" :: Text), "arg0" .= arg0, "arg1" .= arg1, "arg2" .= arg2]
1260 Framebuffer arg0 -> object [ "tag" .= ("Framebuffer" :: Text), "arg0" .= arg0]
1261
1262instance FromJSON ImageRef where
1263 parseJSON (Object obj) = do
1264 tag <- obj .: "tag"
1265 case tag :: Text of
1266 "TextureImage" -> TextureImage <$> obj .: "arg0" <*> obj .: "arg1" <*> obj .: "arg2"
1267 "Framebuffer" -> Framebuffer <$> obj .: "arg0"
1268 parseJSON _ = mzero
1269
1270instance ToJSON ClearImage where
1271 toJSON v = case v of
1272 ClearImage{..} -> object
1273 [ "tag" .= ("ClearImage" :: Text)
1274 , "imageSemantic" .= imageSemantic
1275 , "clearValue" .= clearValue
1276 ]
1277
1278instance FromJSON ClearImage where
1279 parseJSON (Object obj) = do
1280 tag <- obj .: "tag"
1281 case tag :: Text of
1282 "ClearImage" -> do
1283 imageSemantic <- obj .: "imageSemantic"
1284 clearValue <- obj .: "clearValue"
1285 pure $ ClearImage
1286 { imageSemantic = imageSemantic
1287 , clearValue = clearValue
1288 }
1289 parseJSON _ = mzero
1290
1291instance ToJSON Command where
1292 toJSON v = case v of
1293 SetRasterContext arg0 -> object [ "tag" .= ("SetRasterContext" :: Text), "arg0" .= arg0]
1294 SetAccumulationContext arg0 -> object [ "tag" .= ("SetAccumulationContext" :: Text), "arg0" .= arg0]
1295 SetRenderTarget arg0 -> object [ "tag" .= ("SetRenderTarget" :: Text), "arg0" .= arg0]
1296 SetProgram arg0 -> object [ "tag" .= ("SetProgram" :: Text), "arg0" .= arg0]
1297 SetSamplerUniform arg0 arg1 -> object [ "tag" .= ("SetSamplerUniform" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1298 SetTexture arg0 arg1 -> object [ "tag" .= ("SetTexture" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1299 SetSampler arg0 arg1 -> object [ "tag" .= ("SetSampler" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1300 RenderSlot arg0 -> object [ "tag" .= ("RenderSlot" :: Text), "arg0" .= arg0]
1301 RenderStream arg0 -> object [ "tag" .= ("RenderStream" :: Text), "arg0" .= arg0]
1302 ClearRenderTarget arg0 -> object [ "tag" .= ("ClearRenderTarget" :: Text), "arg0" .= arg0]
1303 GenerateMipMap arg0 -> object [ "tag" .= ("GenerateMipMap" :: Text), "arg0" .= arg0]
1304 SaveImage arg0 arg1 -> object [ "tag" .= ("SaveImage" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1305 LoadImage arg0 arg1 -> object [ "tag" .= ("LoadImage" :: Text), "arg0" .= arg0, "arg1" .= arg1]
1306
1307instance FromJSON Command where
1308 parseJSON (Object obj) = do
1309 tag <- obj .: "tag"
1310 case tag :: Text of
1311 "SetRasterContext" -> SetRasterContext <$> obj .: "arg0"
1312 "SetAccumulationContext" -> SetAccumulationContext <$> obj .: "arg0"
1313 "SetRenderTarget" -> SetRenderTarget <$> obj .: "arg0"
1314 "SetProgram" -> SetProgram <$> obj .: "arg0"
1315 "SetSamplerUniform" -> SetSamplerUniform <$> obj .: "arg0" <*> obj .: "arg1"
1316 "SetTexture" -> SetTexture <$> obj .: "arg0" <*> obj .: "arg1"
1317 "SetSampler" -> SetSampler <$> obj .: "arg0" <*> obj .: "arg1"
1318 "RenderSlot" -> RenderSlot <$> obj .: "arg0"
1319 "RenderStream" -> RenderStream <$> obj .: "arg0"
1320 "ClearRenderTarget" -> ClearRenderTarget <$> obj .: "arg0"
1321 "GenerateMipMap" -> GenerateMipMap <$> obj .: "arg0"
1322 "SaveImage" -> SaveImage <$> obj .: "arg0" <*> obj .: "arg1"
1323 "LoadImage" -> LoadImage <$> obj .: "arg0" <*> obj .: "arg1"
1324 parseJSON _ = mzero
1325
1326instance ToJSON SamplerDescriptor where
1327 toJSON v = case v of
1328 SamplerDescriptor{..} -> object
1329 [ "tag" .= ("SamplerDescriptor" :: Text)
1330 , "samplerWrapS" .= samplerWrapS
1331 , "samplerWrapT" .= samplerWrapT
1332 , "samplerWrapR" .= samplerWrapR
1333 , "samplerMinFilter" .= samplerMinFilter
1334 , "samplerMagFilter" .= samplerMagFilter
1335 , "samplerBorderColor" .= samplerBorderColor
1336 , "samplerMinLod" .= samplerMinLod
1337 , "samplerMaxLod" .= samplerMaxLod
1338 , "samplerLodBias" .= samplerLodBias
1339 , "samplerCompareFunc" .= samplerCompareFunc
1340 ]
1341
1342instance FromJSON SamplerDescriptor where
1343 parseJSON (Object obj) = do
1344 tag <- obj .: "tag"
1345 case tag :: Text of
1346 "SamplerDescriptor" -> do
1347 samplerWrapS <- obj .: "samplerWrapS"
1348 samplerWrapT <- obj .: "samplerWrapT"
1349 samplerWrapR <- obj .: "samplerWrapR"
1350 samplerMinFilter <- obj .: "samplerMinFilter"
1351 samplerMagFilter <- obj .: "samplerMagFilter"
1352 samplerBorderColor <- obj .: "samplerBorderColor"
1353 samplerMinLod <- obj .: "samplerMinLod"
1354 samplerMaxLod <- obj .: "samplerMaxLod"
1355 samplerLodBias <- obj .: "samplerLodBias"
1356 samplerCompareFunc <- obj .: "samplerCompareFunc"
1357 pure $ SamplerDescriptor
1358 { samplerWrapS = samplerWrapS
1359 , samplerWrapT = samplerWrapT
1360 , samplerWrapR = samplerWrapR
1361 , samplerMinFilter = samplerMinFilter
1362 , samplerMagFilter = samplerMagFilter
1363 , samplerBorderColor = samplerBorderColor
1364 , samplerMinLod = samplerMinLod
1365 , samplerMaxLod = samplerMaxLod
1366 , samplerLodBias = samplerLodBias
1367 , samplerCompareFunc = samplerCompareFunc
1368 }
1369 parseJSON _ = mzero
1370
1371instance ToJSON TextureDescriptor where
1372 toJSON v = case v of
1373 TextureDescriptor{..} -> object
1374 [ "tag" .= ("TextureDescriptor" :: Text)
1375 , "textureType" .= textureType
1376 , "textureSize" .= textureSize
1377 , "textureSemantic" .= textureSemantic
1378 , "textureSampler" .= textureSampler
1379 , "textureBaseLevel" .= textureBaseLevel
1380 , "textureMaxLevel" .= textureMaxLevel
1381 ]
1382
1383instance FromJSON TextureDescriptor where
1384 parseJSON (Object obj) = do
1385 tag <- obj .: "tag"
1386 case tag :: Text of
1387 "TextureDescriptor" -> do
1388 textureType <- obj .: "textureType"
1389 textureSize <- obj .: "textureSize"
1390 textureSemantic <- obj .: "textureSemantic"
1391 textureSampler <- obj .: "textureSampler"
1392 textureBaseLevel <- obj .: "textureBaseLevel"
1393 textureMaxLevel <- obj .: "textureMaxLevel"
1394 pure $ TextureDescriptor
1395 { textureType = textureType
1396 , textureSize = textureSize
1397 , textureSemantic = textureSemantic
1398 , textureSampler = textureSampler
1399 , textureBaseLevel = textureBaseLevel
1400 , textureMaxLevel = textureMaxLevel
1401 }
1402 parseJSON _ = mzero
1403
1404instance ToJSON Parameter where
1405 toJSON v = case v of
1406 Parameter{..} -> object
1407 [ "tag" .= ("Parameter" :: Text)
1408 , "name" .= name
1409 , "ty" .= ty
1410 ]
1411
1412instance FromJSON Parameter where
1413 parseJSON (Object obj) = do
1414 tag <- obj .: "tag"
1415 case tag :: Text of
1416 "Parameter" -> do
1417 name <- obj .: "name"
1418 ty <- obj .: "ty"
1419 pure $ Parameter
1420 { name = name
1421 , ty = ty
1422 }
1423 parseJSON _ = mzero
1424
1425instance ToJSON Program where
1426 toJSON v = case v of
1427 Program{..} -> object
1428 [ "tag" .= ("Program" :: Text)
1429 , "programUniforms" .= programUniforms
1430 , "programStreams" .= programStreams
1431 , "programInTextures" .= programInTextures
1432 , "programOutput" .= programOutput
1433 , "vertexShader" .= vertexShader
1434 , "geometryShader" .= geometryShader
1435 , "fragmentShader" .= fragmentShader
1436 ]
1437
1438instance FromJSON Program where
1439 parseJSON (Object obj) = do
1440 tag <- obj .: "tag"
1441 case tag :: Text of
1442 "Program" -> do
1443 programUniforms <- obj .: "programUniforms"
1444 programStreams <- obj .: "programStreams"
1445 programInTextures <- obj .: "programInTextures"
1446 programOutput <- obj .: "programOutput"
1447 vertexShader <- obj .: "vertexShader"
1448 geometryShader <- obj .: "geometryShader"
1449 fragmentShader <- obj .: "fragmentShader"
1450 pure $ Program
1451 { programUniforms = programUniforms
1452 , programStreams = programStreams
1453 , programInTextures = programInTextures
1454 , programOutput = programOutput
1455 , vertexShader = vertexShader
1456 , geometryShader = geometryShader
1457 , fragmentShader = fragmentShader
1458 }
1459 parseJSON _ = mzero
1460
1461instance ToJSON Slot where
1462 toJSON v = case v of
1463 Slot{..} -> object
1464 [ "tag" .= ("Slot" :: Text)
1465 , "slotName" .= slotName
1466 , "slotStreams" .= slotStreams
1467 , "slotUniforms" .= slotUniforms
1468 , "slotPrimitive" .= slotPrimitive
1469 , "slotPrograms" .= slotPrograms
1470 ]
1471
1472instance FromJSON Slot where
1473 parseJSON (Object obj) = do
1474 tag <- obj .: "tag"
1475 case tag :: Text of
1476 "Slot" -> do
1477 slotName <- obj .: "slotName"
1478 slotStreams <- obj .: "slotStreams"
1479 slotUniforms <- obj .: "slotUniforms"
1480 slotPrimitive <- obj .: "slotPrimitive"
1481 slotPrograms <- obj .: "slotPrograms"
1482 pure $ Slot
1483 { slotName = slotName
1484 , slotStreams = slotStreams
1485 , slotUniforms = slotUniforms
1486 , slotPrimitive = slotPrimitive
1487 , slotPrograms = slotPrograms
1488 }
1489 parseJSON _ = mzero
1490
1491instance ToJSON StreamData where
1492 toJSON v = case v of
1493 StreamData{..} -> object
1494 [ "tag" .= ("StreamData" :: Text)
1495 , "streamData" .= streamData
1496 , "streamType" .= streamType
1497 , "streamPrimitive" .= streamPrimitive
1498 , "streamPrograms" .= streamPrograms
1499 ]
1500
1501instance FromJSON StreamData where
1502 parseJSON (Object obj) = do
1503 tag <- obj .: "tag"
1504 case tag :: Text of
1505 "StreamData" -> do
1506 streamData <- obj .: "streamData"
1507 streamType <- obj .: "streamType"
1508 streamPrimitive <- obj .: "streamPrimitive"
1509 streamPrograms <- obj .: "streamPrograms"
1510 pure $ StreamData
1511 { streamData = streamData
1512 , streamType = streamType
1513 , streamPrimitive = streamPrimitive
1514 , streamPrograms = streamPrograms
1515 }
1516 parseJSON _ = mzero
1517
1518instance ToJSON TargetItem where
1519 toJSON v = case v of
1520 TargetItem{..} -> object
1521 [ "tag" .= ("TargetItem" :: Text)
1522 , "targetSemantic" .= targetSemantic
1523 , "targetRef" .= targetRef
1524 ]
1525
1526instance FromJSON TargetItem where
1527 parseJSON (Object obj) = do
1528 tag <- obj .: "tag"
1529 case tag :: Text of
1530 "TargetItem" -> do
1531 targetSemantic <- obj .: "targetSemantic"
1532 targetRef <- obj .: "targetRef"
1533 pure $ TargetItem
1534 { targetSemantic = targetSemantic
1535 , targetRef = targetRef
1536 }
1537 parseJSON _ = mzero
1538
1539instance ToJSON RenderTarget where
1540 toJSON v = case v of
1541 RenderTarget{..} -> object
1542 [ "tag" .= ("RenderTarget" :: Text)
1543 , "renderTargets" .= renderTargets
1544 ]
1545
1546instance FromJSON RenderTarget where
1547 parseJSON (Object obj) = do
1548 tag <- obj .: "tag"
1549 case tag :: Text of
1550 "RenderTarget" -> do
1551 renderTargets <- obj .: "renderTargets"
1552 pure $ RenderTarget
1553 { renderTargets = renderTargets
1554 }
1555 parseJSON _ = mzero
1556
1557instance ToJSON Backend where
1558 toJSON v = case v of
1559 WebGL1 -> object [ "tag" .= ("WebGL1" :: Text)]
1560 OpenGL33 -> object [ "tag" .= ("OpenGL33" :: Text)]
1561
1562instance FromJSON Backend where
1563 parseJSON (Object obj) = do
1564 tag <- obj .: "tag"
1565 case tag :: Text of
1566 "WebGL1" -> pure WebGL1
1567 "OpenGL33" -> pure OpenGL33
1568 parseJSON _ = mzero
1569
1570instance ToJSON Pipeline where
1571 toJSON v = case v of
1572 Pipeline{..} -> object
1573 [ "tag" .= ("Pipeline" :: Text)
1574 , "backend" .= backend
1575 , "textures" .= textures
1576 , "samplers" .= samplers
1577 , "targets" .= targets
1578 , "programs" .= programs
1579 , "slots" .= slots
1580 , "streams" .= streams
1581 , "commands" .= commands
1582 ]
1583
1584instance FromJSON Pipeline where
1585 parseJSON (Object obj) = do
1586 tag <- obj .: "tag"
1587 case tag :: Text of
1588 "Pipeline" -> do
1589 backend <- obj .: "backend"
1590 textures <- obj .: "textures"
1591 samplers <- obj .: "samplers"
1592 targets <- obj .: "targets"
1593 programs <- obj .: "programs"
1594 slots <- obj .: "slots"
1595 streams <- obj .: "streams"
1596 commands <- obj .: "commands"
1597 pure $ Pipeline
1598 { backend = backend
1599 , textures = textures
1600 , samplers = samplers
1601 , targets = targets
1602 , programs = programs
1603 , slots = slots
1604 , streams = streams
1605 , commands = commands
1606 }
1607 parseJSON _ = mzero
1608
diff --git a/ddl/out/IR.purs b/ddl/out/IR.purs
new file mode 100644
index 0000000..801e3f9
--- /dev/null
+++ b/ddl/out/IR.purs
@@ -0,0 +1,1590 @@
1-- generated file, do not modify!
2-- 2015-12-21T12:00:19.420877000000Z
3
4module 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
diff --git a/ddl/out/IR.swift b/ddl/out/IR.swift
new file mode 100644
index 0000000..c30e6d7
--- /dev/null
+++ b/ddl/out/IR.swift
@@ -0,0 +1,1429 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.420877000000Z
3
4typealias StreamName = Int
5
6typealias ProgramName = Int
7
8typealias TextureName = Int
9
10typealias SamplerName = Int
11
12typealias UniformName = String
13
14typealias SlotName = Int
15
16typealias FrameBufferComponent = Int
17
18typealias TextureUnit = Int
19
20typealias RenderTargetName = Int
21
22typealias TextureUnitMapping = Dictionary<UniformName, TextureUnit>
23
24enum ArrayValue {
25 case VBoolArray(Array<Bool>)
26 case VIntArray(Array<Int32>)
27 case VWordArray(Array<UInt32>)
28 case VFloatArray(Array<Float>)
29}
30
31enum Value {
32 case VBool(Bool)
33 case VV2B(Int)
34 case VV3B(Int)
35 case VV4B(Int)
36 case VWord(UInt32)
37 case VV2U(Int)
38 case VV3U(Int)
39 case VV4U(Int)
40 case VInt(Int32)
41 case VV2I(Int)
42 case VV3I(Int)
43 case VV4I(Int)
44 case VFloat(Float)
45 case VV2F(Int)
46 case VV3F(Int)
47 case VV4F(Int)
48 case VM22F(Int)
49 case VM23F(Int)
50 case VM24F(Int)
51 case VM32F(Int)
52 case VM33F(Int)
53 case VM34F(Int)
54 case VM42F(Int)
55 case VM43F(Int)
56 case VM44F(Int)
57}
58
59enum InputType {
60 case Bool
61 case V2B
62 case V3B
63 case V4B
64 case Word
65 case V2U
66 case V3U
67 case V4U
68 case Int
69 case V2I
70 case V3I
71 case V4I
72 case Float
73 case V2F
74 case V3F
75 case V4F
76 case M22F
77 case M23F
78 case M24F
79 case M32F
80 case M33F
81 case M34F
82 case M42F
83 case M43F
84 case M44F
85 case STexture1D
86 case STexture2D
87 case STextureCube
88 case STexture1DArray
89 case STexture2DArray
90 case STexture2DRect
91 case FTexture1D
92 case FTexture2D
93 case FTexture3D
94 case FTextureCube
95 case FTexture1DArray
96 case FTexture2DArray
97 case FTexture2DMS
98 case FTexture2DMSArray
99 case FTextureBuffer
100 case FTexture2DRect
101 case ITexture1D
102 case ITexture2D
103 case ITexture3D
104 case ITextureCube
105 case ITexture1DArray
106 case ITexture2DArray
107 case ITexture2DMS
108 case ITexture2DMSArray
109 case ITextureBuffer
110 case ITexture2DRect
111 case UTexture1D
112 case UTexture2D
113 case UTexture3D
114 case UTextureCube
115 case UTexture1DArray
116 case UTexture2DArray
117 case UTexture2DMS
118 case UTexture2DMSArray
119 case UTextureBuffer
120 case UTexture2DRect
121}
122
123enum PointSpriteCoordOrigin {
124 case LowerLeft
125 case UpperLeft
126}
127
128enum PointSize {
129 case PointSize(Float)
130 case ProgramPointSize
131}
132
133enum PolygonOffset {
134 case NoOffset
135 case Offset(Float,Float)
136}
137
138enum FrontFace {
139 case CCW
140 case CW
141}
142
143enum PolygonMode {
144 case PolygonPoint(PointSize)
145 case PolygonLine(Float)
146 case PolygonFill
147}
148
149enum ProvokingVertex {
150 case FirstVertex
151 case LastVertex
152}
153
154enum CullMode {
155 case CullNone
156 case CullFront(FrontFace)
157 case CullBack(FrontFace)
158}
159
160enum ComparisonFunction {
161 case Never
162 case Less
163 case Equal
164 case Lequal
165 case Greater
166 case Notequal
167 case Gequal
168 case Always
169}
170
171typealias DepthFunction = ComparisonFunction
172
173enum StencilOperation {
174 case OpZero
175 case OpKeep
176 case OpReplace
177 case OpIncr
178 case OpIncrWrap
179 case OpDecr
180 case OpDecrWrap
181 case OpInvert
182}
183
184enum BlendEquation {
185 case FuncAdd
186 case FuncSubtract
187 case FuncReverseSubtract
188 case Min
189 case Max
190}
191
192enum BlendingFactor {
193 case Zero
194 case One
195 case SrcColor
196 case OneMinusSrcColor
197 case DstColor
198 case OneMinusDstColor
199 case SrcAlpha
200 case OneMinusSrcAlpha
201 case DstAlpha
202 case OneMinusDstAlpha
203 case ConstantColor
204 case OneMinusConstantColor
205 case ConstantAlpha
206 case OneMinusConstantAlpha
207 case SrcAlphaSaturate
208}
209
210enum LogicOperation {
211 case Clear
212 case And
213 case AndReverse
214 case Copy
215 case AndInverted
216 case Noop
217 case Xor
218 case Or
219 case Nor
220 case Equiv
221 case Invert
222 case OrReverse
223 case CopyInverted
224 case OrInverted
225 case Nand
226 case Set
227}
228
229enum StencilOps {
230 case StencilOps(StencilOps_Data)
231 struct StencilOps_Data {
232 var frontStencilOp : StencilOperation
233 var backStencilOp : StencilOperation
234 }
235}
236
237enum StencilTest {
238 case StencilTest(StencilTest_Data)
239 struct StencilTest_Data {
240 var stencilComparision : ComparisonFunction
241 var stencilReference : Int32
242 var stencilMask : UInt32
243 }
244}
245
246enum StencilTests {
247 case StencilTests(StencilTest,StencilTest)
248}
249
250enum FetchPrimitive {
251 case Points
252 case Lines
253 case Triangles
254 case LinesAdjacency
255 case TrianglesAdjacency
256}
257
258enum OutputPrimitive {
259 case TrianglesOutput
260 case LinesOutput
261 case PointsOutput
262}
263
264enum ColorArity {
265 case Red
266 case RG
267 case RGB
268 case RGBA
269}
270
271enum Blending {
272 case NoBlending
273 case BlendLogicOp(LogicOperation)
274 case Blend(Blend_Data)
275 struct Blend_Data {
276 var colorEqSrc : BlendEquation
277 var alphaEqSrc : BlendEquation
278 var colorFSrc : BlendingFactor
279 var colorFDst : BlendingFactor
280 var alphaFSrc : BlendingFactor
281 var alphaFDst : BlendingFactor
282 var color : Int
283 }
284}
285
286enum RasterContext {
287 case PointCtx(PointSize,Float,PointSpriteCoordOrigin)
288 case LineCtx(Float,ProvokingVertex)
289 case TriangleCtx(CullMode,PolygonMode,PolygonOffset,ProvokingVertex)
290}
291
292enum FragmentOperation {
293 case DepthOp(DepthFunction,Bool)
294 case StencilOp(StencilTests,StencilOps,StencilOps)
295 case ColorOp(Blending,Value)
296}
297
298enum AccumulationContext {
299 case AccumulationContext(AccumulationContext_Data)
300 struct AccumulationContext_Data {
301 var accViewportName : Maybe<String>
302 var accOperations : Array<FragmentOperation>
303 }
304}
305
306enum TextureDataType {
307 case FloatT(ColorArity)
308 case IntT(ColorArity)
309 case WordT(ColorArity)
310 case ShadowT
311}
312
313enum TextureType {
314 case Texture1D(TextureDataType,Int)
315 case Texture2D(TextureDataType,Int)
316 case Texture3D(TextureDataType)
317 case TextureCube(TextureDataType)
318 case TextureRect(TextureDataType)
319 case Texture2DMS(TextureDataType,Int,Int,Bool)
320 case TextureBuffer(TextureDataType)
321}
322
323enum MipMap {
324 case Mip(Int,Int)
325 case NoMip
326 case AutoMip(Int,Int)
327}
328
329enum Filter {
330 case Nearest
331 case Linear
332 case NearestMipmapNearest
333 case NearestMipmapLinear
334 case LinearMipmapNearest
335 case LinearMipmapLinear
336}
337
338enum EdgeMode {
339 case Repeat
340 case MirroredRepeat
341 case ClampToEdge
342 case ClampToBorder
343}
344
345enum ImageSemantic {
346 case Depth
347 case Stencil
348 case Color
349}
350
351enum ImageRef {
352 case TextureImage(TextureName,Int,Maybe<Int>)
353 case Framebuffer(ImageSemantic)
354}
355
356enum ClearImage {
357 case ClearImage(ClearImage_Data)
358 struct ClearImage_Data {
359 var imageSemantic : ImageSemantic
360 var clearValue : Value
361 }
362}
363
364enum Command {
365 case SetRasterContext(RasterContext)
366 case SetAccumulationContext(AccumulationContext)
367 case SetRenderTarget(RenderTargetName)
368 case SetProgram(ProgramName)
369 case SetSamplerUniform(UniformName,TextureUnit)
370 case SetTexture(TextureUnit,TextureName)
371 case SetSampler(TextureUnit,Maybe<SamplerName>)
372 case RenderSlot(SlotName)
373 case RenderStream(StreamName)
374 case ClearRenderTarget(Array<ClearImage>)
375 case GenerateMipMap(TextureUnit)
376 case SaveImage(FrameBufferComponent,ImageRef)
377 case LoadImage(ImageRef,FrameBufferComponent)
378}
379
380enum SamplerDescriptor {
381 case SamplerDescriptor(SamplerDescriptor_Data)
382 struct SamplerDescriptor_Data {
383 var samplerWrapS : EdgeMode
384 var samplerWrapT : Maybe<EdgeMode>
385 var samplerWrapR : Maybe<EdgeMode>
386 var samplerMinFilter : Filter
387 var samplerMagFilter : Filter
388 var samplerBorderColor : Value
389 var samplerMinLod : Maybe<Float>
390 var samplerMaxLod : Maybe<Float>
391 var samplerLodBias : Float
392 var samplerCompareFunc : Maybe<ComparisonFunction>
393 }
394}
395
396enum TextureDescriptor {
397 case TextureDescriptor(TextureDescriptor_Data)
398 struct TextureDescriptor_Data {
399 var textureType : TextureType
400 var textureSize : Value
401 var textureSemantic : ImageSemantic
402 var textureSampler : SamplerDescriptor
403 var textureBaseLevel : Int
404 var textureMaxLevel : Int
405 }
406}
407
408enum Parameter {
409 case Parameter(Parameter_Data)
410 struct Parameter_Data {
411 var name : String
412 var ty : InputType
413 }
414}
415
416enum Program {
417 case Program(Program_Data)
418 struct Program_Data {
419 var programUniforms : Dictionary<UniformName, InputType>
420 var programStreams : Dictionary<UniformName, Parameter>
421 var programInTextures : Dictionary<UniformName, InputType>
422 var programOutput : Array<Parameter>
423 var vertexShader : String
424 var geometryShader : Maybe<String>
425 var fragmentShader : String
426 }
427}
428
429enum Slot {
430 case Slot(Slot_Data)
431 struct Slot_Data {
432 var slotName : String
433 var slotStreams : Dictionary<String, InputType>
434 var slotUniforms : Dictionary<UniformName, InputType>
435 var slotPrimitive : FetchPrimitive
436 var slotPrograms : Array<ProgramName>
437 }
438}
439
440enum StreamData {
441 case StreamData(StreamData_Data)
442 struct StreamData_Data {
443 var streamData : Dictionary<String, ArrayValue>
444 var streamType : Dictionary<String, InputType>
445 var streamPrimitive : FetchPrimitive
446 var streamPrograms : Array<ProgramName>
447 }
448}
449
450enum TargetItem {
451 case TargetItem(TargetItem_Data)
452 struct TargetItem_Data {
453 var targetSemantic : ImageSemantic
454 var targetRef : Maybe<ImageRef>
455 }
456}
457
458enum RenderTarget {
459 case RenderTarget(RenderTarget_Data)
460 struct RenderTarget_Data {
461 var renderTargets : Array<TargetItem>
462 }
463}
464
465enum Backend {
466 case WebGL1
467 case OpenGL33
468}
469
470enum Pipeline {
471 case Pipeline(Pipeline_Data)
472 struct Pipeline_Data {
473 var backend : Backend
474 var textures : Array<TextureDescriptor>
475 var samplers : Array<SamplerDescriptor>
476 var targets : Array<RenderTarget>
477 var programs : Array<Program>
478 var slots : Array<Slot>
479 var streams : Array<StreamData>
480 var commands : Array<Command>
481 }
482}
483
484
485extension Int {
486 var toJSON : [String: AnyObject] {
487 return ["":""]
488 }
489}
490extension Int32 {
491 var toJSON : [String: AnyObject] {
492 return ["":""]
493 }
494}
495extension UInt {
496 var toJSON : [String: AnyObject] {
497 return ["":""]
498 }
499}
500extension UInt32 {
501 var toJSON : [String: AnyObject] {
502 return ["":""]
503 }
504}
505extension Float {
506 var toJSON : [String: AnyObject] {
507 return ["":""]
508 }
509}
510extension Bool {
511 var toJSON : [String: AnyObject] {
512 return ["":""]
513 }
514}
515extension String {
516 var toJSON : [String: AnyObject] {
517 return ["":""]
518 }
519}
520extension Array {
521 var toJSON : [String: AnyObject] {
522 return ["":""]
523 }
524}
525extension Dictionary {
526 var toJSON : [String: AnyObject] {
527 return ["":""]
528 }
529}
530extension Maybe {
531 var toJSON : [String: AnyObject] {
532 return ["":""]
533 }
534}
535
536
537
538extension ArrayValue {
539 var toJSON : [String: AnyObject] {
540 switch self {
541 case .VBoolArray(let arg0):
542 return [ "tag" : "VBoolArray", "arg0" : arg0.toJSON]
543 case .VIntArray(let arg0):
544 return [ "tag" : "VIntArray", "arg0" : arg0.toJSON]
545 case .VWordArray(let arg0):
546 return [ "tag" : "VWordArray", "arg0" : arg0.toJSON]
547 case .VFloatArray(let arg0):
548 return [ "tag" : "VFloatArray", "arg0" : arg0.toJSON]
549 }
550 }
551}
552extension Value {
553 var toJSON : [String: AnyObject] {
554 switch self {
555 case .VBool(let arg0):
556 return [ "tag" : "VBool", "arg0" : arg0.toJSON]
557 case .VV2B(let arg0):
558 return [ "tag" : "VV2B", "arg0" : arg0.toJSON]
559 case .VV3B(let arg0):
560 return [ "tag" : "VV3B", "arg0" : arg0.toJSON]
561 case .VV4B(let arg0):
562 return [ "tag" : "VV4B", "arg0" : arg0.toJSON]
563 case .VWord(let arg0):
564 return [ "tag" : "VWord", "arg0" : arg0.toJSON]
565 case .VV2U(let arg0):
566 return [ "tag" : "VV2U", "arg0" : arg0.toJSON]
567 case .VV3U(let arg0):
568 return [ "tag" : "VV3U", "arg0" : arg0.toJSON]
569 case .VV4U(let arg0):
570 return [ "tag" : "VV4U", "arg0" : arg0.toJSON]
571 case .VInt(let arg0):
572 return [ "tag" : "VInt", "arg0" : arg0.toJSON]
573 case .VV2I(let arg0):
574 return [ "tag" : "VV2I", "arg0" : arg0.toJSON]
575 case .VV3I(let arg0):
576 return [ "tag" : "VV3I", "arg0" : arg0.toJSON]
577 case .VV4I(let arg0):
578 return [ "tag" : "VV4I", "arg0" : arg0.toJSON]
579 case .VFloat(let arg0):
580 return [ "tag" : "VFloat", "arg0" : arg0.toJSON]
581 case .VV2F(let arg0):
582 return [ "tag" : "VV2F", "arg0" : arg0.toJSON]
583 case .VV3F(let arg0):
584 return [ "tag" : "VV3F", "arg0" : arg0.toJSON]
585 case .VV4F(let arg0):
586 return [ "tag" : "VV4F", "arg0" : arg0.toJSON]
587 case .VM22F(let arg0):
588 return [ "tag" : "VM22F", "arg0" : arg0.toJSON]
589 case .VM23F(let arg0):
590 return [ "tag" : "VM23F", "arg0" : arg0.toJSON]
591 case .VM24F(let arg0):
592 return [ "tag" : "VM24F", "arg0" : arg0.toJSON]
593 case .VM32F(let arg0):
594 return [ "tag" : "VM32F", "arg0" : arg0.toJSON]
595 case .VM33F(let arg0):
596 return [ "tag" : "VM33F", "arg0" : arg0.toJSON]
597 case .VM34F(let arg0):
598 return [ "tag" : "VM34F", "arg0" : arg0.toJSON]
599 case .VM42F(let arg0):
600 return [ "tag" : "VM42F", "arg0" : arg0.toJSON]
601 case .VM43F(let arg0):
602 return [ "tag" : "VM43F", "arg0" : arg0.toJSON]
603 case .VM44F(let arg0):
604 return [ "tag" : "VM44F", "arg0" : arg0.toJSON]
605 }
606 }
607}
608extension InputType {
609 var toJSON : [String: AnyObject] {
610 switch self {
611 case .Bool:
612 return [ "tag" : "Bool"]
613 case .V2B:
614 return [ "tag" : "V2B"]
615 case .V3B:
616 return [ "tag" : "V3B"]
617 case .V4B:
618 return [ "tag" : "V4B"]
619 case .Word:
620 return [ "tag" : "Word"]
621 case .V2U:
622 return [ "tag" : "V2U"]
623 case .V3U:
624 return [ "tag" : "V3U"]
625 case .V4U:
626 return [ "tag" : "V4U"]
627 case .Int:
628 return [ "tag" : "Int"]
629 case .V2I:
630 return [ "tag" : "V2I"]
631 case .V3I:
632 return [ "tag" : "V3I"]
633 case .V4I:
634 return [ "tag" : "V4I"]
635 case .Float:
636 return [ "tag" : "Float"]
637 case .V2F:
638 return [ "tag" : "V2F"]
639 case .V3F:
640 return [ "tag" : "V3F"]
641 case .V4F:
642 return [ "tag" : "V4F"]
643 case .M22F:
644 return [ "tag" : "M22F"]
645 case .M23F:
646 return [ "tag" : "M23F"]
647 case .M24F:
648 return [ "tag" : "M24F"]
649 case .M32F:
650 return [ "tag" : "M32F"]
651 case .M33F:
652 return [ "tag" : "M33F"]
653 case .M34F:
654 return [ "tag" : "M34F"]
655 case .M42F:
656 return [ "tag" : "M42F"]
657 case .M43F:
658 return [ "tag" : "M43F"]
659 case .M44F:
660 return [ "tag" : "M44F"]
661 case .STexture1D:
662 return [ "tag" : "STexture1D"]
663 case .STexture2D:
664 return [ "tag" : "STexture2D"]
665 case .STextureCube:
666 return [ "tag" : "STextureCube"]
667 case .STexture1DArray:
668 return [ "tag" : "STexture1DArray"]
669 case .STexture2DArray:
670 return [ "tag" : "STexture2DArray"]
671 case .STexture2DRect:
672 return [ "tag" : "STexture2DRect"]
673 case .FTexture1D:
674 return [ "tag" : "FTexture1D"]
675 case .FTexture2D:
676 return [ "tag" : "FTexture2D"]
677 case .FTexture3D:
678 return [ "tag" : "FTexture3D"]
679 case .FTextureCube:
680 return [ "tag" : "FTextureCube"]
681 case .FTexture1DArray:
682 return [ "tag" : "FTexture1DArray"]
683 case .FTexture2DArray:
684 return [ "tag" : "FTexture2DArray"]
685 case .FTexture2DMS:
686 return [ "tag" : "FTexture2DMS"]
687 case .FTexture2DMSArray:
688 return [ "tag" : "FTexture2DMSArray"]
689 case .FTextureBuffer:
690 return [ "tag" : "FTextureBuffer"]
691 case .FTexture2DRect:
692 return [ "tag" : "FTexture2DRect"]
693 case .ITexture1D:
694 return [ "tag" : "ITexture1D"]
695 case .ITexture2D:
696 return [ "tag" : "ITexture2D"]
697 case .ITexture3D:
698 return [ "tag" : "ITexture3D"]
699 case .ITextureCube:
700 return [ "tag" : "ITextureCube"]
701 case .ITexture1DArray:
702 return [ "tag" : "ITexture1DArray"]
703 case .ITexture2DArray:
704 return [ "tag" : "ITexture2DArray"]
705 case .ITexture2DMS:
706 return [ "tag" : "ITexture2DMS"]
707 case .ITexture2DMSArray:
708 return [ "tag" : "ITexture2DMSArray"]
709 case .ITextureBuffer:
710 return [ "tag" : "ITextureBuffer"]
711 case .ITexture2DRect:
712 return [ "tag" : "ITexture2DRect"]
713 case .UTexture1D:
714 return [ "tag" : "UTexture1D"]
715 case .UTexture2D:
716 return [ "tag" : "UTexture2D"]
717 case .UTexture3D:
718 return [ "tag" : "UTexture3D"]
719 case .UTextureCube:
720 return [ "tag" : "UTextureCube"]
721 case .UTexture1DArray:
722 return [ "tag" : "UTexture1DArray"]
723 case .UTexture2DArray:
724 return [ "tag" : "UTexture2DArray"]
725 case .UTexture2DMS:
726 return [ "tag" : "UTexture2DMS"]
727 case .UTexture2DMSArray:
728 return [ "tag" : "UTexture2DMSArray"]
729 case .UTextureBuffer:
730 return [ "tag" : "UTextureBuffer"]
731 case .UTexture2DRect:
732 return [ "tag" : "UTexture2DRect"]
733 }
734 }
735}
736extension PointSpriteCoordOrigin {
737 var toJSON : [String: AnyObject] {
738 switch self {
739 case .LowerLeft:
740 return [ "tag" : "LowerLeft"]
741 case .UpperLeft:
742 return [ "tag" : "UpperLeft"]
743 }
744 }
745}
746extension PointSize {
747 var toJSON : [String: AnyObject] {
748 switch self {
749 case .PointSize(let arg0):
750 return [ "tag" : "PointSize", "arg0" : arg0.toJSON]
751 case .ProgramPointSize:
752 return [ "tag" : "ProgramPointSize"]
753 }
754 }
755}
756extension PolygonOffset {
757 var toJSON : [String: AnyObject] {
758 switch self {
759 case .NoOffset:
760 return [ "tag" : "NoOffset"]
761 case .Offset(let arg0, let arg1):
762 return [ "tag" : "Offset", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
763 }
764 }
765}
766extension FrontFace {
767 var toJSON : [String: AnyObject] {
768 switch self {
769 case .CCW:
770 return [ "tag" : "CCW"]
771 case .CW:
772 return [ "tag" : "CW"]
773 }
774 }
775}
776extension PolygonMode {
777 var toJSON : [String: AnyObject] {
778 switch self {
779 case .PolygonPoint(let arg0):
780 return [ "tag" : "PolygonPoint", "arg0" : arg0.toJSON]
781 case .PolygonLine(let arg0):
782 return [ "tag" : "PolygonLine", "arg0" : arg0.toJSON]
783 case .PolygonFill:
784 return [ "tag" : "PolygonFill"]
785 }
786 }
787}
788extension ProvokingVertex {
789 var toJSON : [String: AnyObject] {
790 switch self {
791 case .FirstVertex:
792 return [ "tag" : "FirstVertex"]
793 case .LastVertex:
794 return [ "tag" : "LastVertex"]
795 }
796 }
797}
798extension CullMode {
799 var toJSON : [String: AnyObject] {
800 switch self {
801 case .CullNone:
802 return [ "tag" : "CullNone"]
803 case .CullFront(let arg0):
804 return [ "tag" : "CullFront", "arg0" : arg0.toJSON]
805 case .CullBack(let arg0):
806 return [ "tag" : "CullBack", "arg0" : arg0.toJSON]
807 }
808 }
809}
810extension ComparisonFunction {
811 var toJSON : [String: AnyObject] {
812 switch self {
813 case .Never:
814 return [ "tag" : "Never"]
815 case .Less:
816 return [ "tag" : "Less"]
817 case .Equal:
818 return [ "tag" : "Equal"]
819 case .Lequal:
820 return [ "tag" : "Lequal"]
821 case .Greater:
822 return [ "tag" : "Greater"]
823 case .Notequal:
824 return [ "tag" : "Notequal"]
825 case .Gequal:
826 return [ "tag" : "Gequal"]
827 case .Always:
828 return [ "tag" : "Always"]
829 }
830 }
831}
832extension StencilOperation {
833 var toJSON : [String: AnyObject] {
834 switch self {
835 case .OpZero:
836 return [ "tag" : "OpZero"]
837 case .OpKeep:
838 return [ "tag" : "OpKeep"]
839 case .OpReplace:
840 return [ "tag" : "OpReplace"]
841 case .OpIncr:
842 return [ "tag" : "OpIncr"]
843 case .OpIncrWrap:
844 return [ "tag" : "OpIncrWrap"]
845 case .OpDecr:
846 return [ "tag" : "OpDecr"]
847 case .OpDecrWrap:
848 return [ "tag" : "OpDecrWrap"]
849 case .OpInvert:
850 return [ "tag" : "OpInvert"]
851 }
852 }
853}
854extension BlendEquation {
855 var toJSON : [String: AnyObject] {
856 switch self {
857 case .FuncAdd:
858 return [ "tag" : "FuncAdd"]
859 case .FuncSubtract:
860 return [ "tag" : "FuncSubtract"]
861 case .FuncReverseSubtract:
862 return [ "tag" : "FuncReverseSubtract"]
863 case .Min:
864 return [ "tag" : "Min"]
865 case .Max:
866 return [ "tag" : "Max"]
867 }
868 }
869}
870extension BlendingFactor {
871 var toJSON : [String: AnyObject] {
872 switch self {
873 case .Zero:
874 return [ "tag" : "Zero"]
875 case .One:
876 return [ "tag" : "One"]
877 case .SrcColor:
878 return [ "tag" : "SrcColor"]
879 case .OneMinusSrcColor:
880 return [ "tag" : "OneMinusSrcColor"]
881 case .DstColor:
882 return [ "tag" : "DstColor"]
883 case .OneMinusDstColor:
884 return [ "tag" : "OneMinusDstColor"]
885 case .SrcAlpha:
886 return [ "tag" : "SrcAlpha"]
887 case .OneMinusSrcAlpha:
888 return [ "tag" : "OneMinusSrcAlpha"]
889 case .DstAlpha:
890 return [ "tag" : "DstAlpha"]
891 case .OneMinusDstAlpha:
892 return [ "tag" : "OneMinusDstAlpha"]
893 case .ConstantColor:
894 return [ "tag" : "ConstantColor"]
895 case .OneMinusConstantColor:
896 return [ "tag" : "OneMinusConstantColor"]
897 case .ConstantAlpha:
898 return [ "tag" : "ConstantAlpha"]
899 case .OneMinusConstantAlpha:
900 return [ "tag" : "OneMinusConstantAlpha"]
901 case .SrcAlphaSaturate:
902 return [ "tag" : "SrcAlphaSaturate"]
903 }
904 }
905}
906extension LogicOperation {
907 var toJSON : [String: AnyObject] {
908 switch self {
909 case .Clear:
910 return [ "tag" : "Clear"]
911 case .And:
912 return [ "tag" : "And"]
913 case .AndReverse:
914 return [ "tag" : "AndReverse"]
915 case .Copy:
916 return [ "tag" : "Copy"]
917 case .AndInverted:
918 return [ "tag" : "AndInverted"]
919 case .Noop:
920 return [ "tag" : "Noop"]
921 case .Xor:
922 return [ "tag" : "Xor"]
923 case .Or:
924 return [ "tag" : "Or"]
925 case .Nor:
926 return [ "tag" : "Nor"]
927 case .Equiv:
928 return [ "tag" : "Equiv"]
929 case .Invert:
930 return [ "tag" : "Invert"]
931 case .OrReverse:
932 return [ "tag" : "OrReverse"]
933 case .CopyInverted:
934 return [ "tag" : "CopyInverted"]
935 case .OrInverted:
936 return [ "tag" : "OrInverted"]
937 case .Nand:
938 return [ "tag" : "Nand"]
939 case .Set:
940 return [ "tag" : "Set"]
941 }
942 }
943}
944extension StencilOps {
945 var toJSON : [String: AnyObject] {
946 switch self {
947 case .StencilOps(let v):
948 return [ "tag" : "StencilOps"
949 , "frontStencilOp" : v.frontStencilOp.toJSON
950 , "backStencilOp" : v.backStencilOp.toJSON
951 ]
952 }
953 }
954}
955extension StencilTest {
956 var toJSON : [String: AnyObject] {
957 switch self {
958 case .StencilTest(let v):
959 return [ "tag" : "StencilTest"
960 , "stencilComparision" : v.stencilComparision.toJSON
961 , "stencilReference" : v.stencilReference.toJSON
962 , "stencilMask" : v.stencilMask.toJSON
963 ]
964 }
965 }
966}
967extension StencilTests {
968 var toJSON : [String: AnyObject] {
969 switch self {
970 case .StencilTests(let arg0, let arg1):
971 return [ "tag" : "StencilTests", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
972 }
973 }
974}
975extension FetchPrimitive {
976 var toJSON : [String: AnyObject] {
977 switch self {
978 case .Points:
979 return [ "tag" : "Points"]
980 case .Lines:
981 return [ "tag" : "Lines"]
982 case .Triangles:
983 return [ "tag" : "Triangles"]
984 case .LinesAdjacency:
985 return [ "tag" : "LinesAdjacency"]
986 case .TrianglesAdjacency:
987 return [ "tag" : "TrianglesAdjacency"]
988 }
989 }
990}
991extension OutputPrimitive {
992 var toJSON : [String: AnyObject] {
993 switch self {
994 case .TrianglesOutput:
995 return [ "tag" : "TrianglesOutput"]
996 case .LinesOutput:
997 return [ "tag" : "LinesOutput"]
998 case .PointsOutput:
999 return [ "tag" : "PointsOutput"]
1000 }
1001 }
1002}
1003extension ColorArity {
1004 var toJSON : [String: AnyObject] {
1005 switch self {
1006 case .Red:
1007 return [ "tag" : "Red"]
1008 case .RG:
1009 return [ "tag" : "RG"]
1010 case .RGB:
1011 return [ "tag" : "RGB"]
1012 case .RGBA:
1013 return [ "tag" : "RGBA"]
1014 }
1015 }
1016}
1017extension Blending {
1018 var toJSON : [String: AnyObject] {
1019 switch self {
1020 case .NoBlending:
1021 return [ "tag" : "NoBlending"]
1022 case .BlendLogicOp(let arg0):
1023 return [ "tag" : "BlendLogicOp", "arg0" : arg0.toJSON]
1024 case .Blend(let v):
1025 return [ "tag" : "Blend"
1026 , "colorEqSrc" : v.colorEqSrc.toJSON
1027 , "alphaEqSrc" : v.alphaEqSrc.toJSON
1028 , "colorFSrc" : v.colorFSrc.toJSON
1029 , "colorFDst" : v.colorFDst.toJSON
1030 , "alphaFSrc" : v.alphaFSrc.toJSON
1031 , "alphaFDst" : v.alphaFDst.toJSON
1032 , "color" : v.color.toJSON
1033 ]
1034 }
1035 }
1036}
1037extension RasterContext {
1038 var toJSON : [String: AnyObject] {
1039 switch self {
1040 case .PointCtx(let arg0, let arg1, let arg2):
1041 return [ "tag" : "PointCtx", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON, "arg2" : arg2.toJSON]
1042 case .LineCtx(let arg0, let arg1):
1043 return [ "tag" : "LineCtx", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1044 case .TriangleCtx(let arg0, let arg1, let arg2, let arg3):
1045 return [ "tag" : "TriangleCtx", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON, "arg2" : arg2.toJSON, "arg3" : arg3.toJSON]
1046 }
1047 }
1048}
1049extension FragmentOperation {
1050 var toJSON : [String: AnyObject] {
1051 switch self {
1052 case .DepthOp(let arg0, let arg1):
1053 return [ "tag" : "DepthOp", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1054 case .StencilOp(let arg0, let arg1, let arg2):
1055 return [ "tag" : "StencilOp", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON, "arg2" : arg2.toJSON]
1056 case .ColorOp(let arg0, let arg1):
1057 return [ "tag" : "ColorOp", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1058 }
1059 }
1060}
1061extension AccumulationContext {
1062 var toJSON : [String: AnyObject] {
1063 switch self {
1064 case .AccumulationContext(let v):
1065 return [ "tag" : "AccumulationContext"
1066 , "accViewportName" : v.accViewportName.toJSON
1067 , "accOperations" : v.accOperations.toJSON
1068 ]
1069 }
1070 }
1071}
1072extension TextureDataType {
1073 var toJSON : [String: AnyObject] {
1074 switch self {
1075 case .FloatT(let arg0):
1076 return [ "tag" : "FloatT", "arg0" : arg0.toJSON]
1077 case .IntT(let arg0):
1078 return [ "tag" : "IntT", "arg0" : arg0.toJSON]
1079 case .WordT(let arg0):
1080 return [ "tag" : "WordT", "arg0" : arg0.toJSON]
1081 case .ShadowT:
1082 return [ "tag" : "ShadowT"]
1083 }
1084 }
1085}
1086extension TextureType {
1087 var toJSON : [String: AnyObject] {
1088 switch self {
1089 case .Texture1D(let arg0, let arg1):
1090 return [ "tag" : "Texture1D", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1091 case .Texture2D(let arg0, let arg1):
1092 return [ "tag" : "Texture2D", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1093 case .Texture3D(let arg0):
1094 return [ "tag" : "Texture3D", "arg0" : arg0.toJSON]
1095 case .TextureCube(let arg0):
1096 return [ "tag" : "TextureCube", "arg0" : arg0.toJSON]
1097 case .TextureRect(let arg0):
1098 return [ "tag" : "TextureRect", "arg0" : arg0.toJSON]
1099 case .Texture2DMS(let arg0, let arg1, let arg2, let arg3):
1100 return [ "tag" : "Texture2DMS", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON, "arg2" : arg2.toJSON, "arg3" : arg3.toJSON]
1101 case .TextureBuffer(let arg0):
1102 return [ "tag" : "TextureBuffer", "arg0" : arg0.toJSON]
1103 }
1104 }
1105}
1106extension MipMap {
1107 var toJSON : [String: AnyObject] {
1108 switch self {
1109 case .Mip(let arg0, let arg1):
1110 return [ "tag" : "Mip", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1111 case .NoMip:
1112 return [ "tag" : "NoMip"]
1113 case .AutoMip(let arg0, let arg1):
1114 return [ "tag" : "AutoMip", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1115 }
1116 }
1117}
1118extension Filter {
1119 var toJSON : [String: AnyObject] {
1120 switch self {
1121 case .Nearest:
1122 return [ "tag" : "Nearest"]
1123 case .Linear:
1124 return [ "tag" : "Linear"]
1125 case .NearestMipmapNearest:
1126 return [ "tag" : "NearestMipmapNearest"]
1127 case .NearestMipmapLinear:
1128 return [ "tag" : "NearestMipmapLinear"]
1129 case .LinearMipmapNearest:
1130 return [ "tag" : "LinearMipmapNearest"]
1131 case .LinearMipmapLinear:
1132 return [ "tag" : "LinearMipmapLinear"]
1133 }
1134 }
1135}
1136extension EdgeMode {
1137 var toJSON : [String: AnyObject] {
1138 switch self {
1139 case .Repeat:
1140 return [ "tag" : "Repeat"]
1141 case .MirroredRepeat:
1142 return [ "tag" : "MirroredRepeat"]
1143 case .ClampToEdge:
1144 return [ "tag" : "ClampToEdge"]
1145 case .ClampToBorder:
1146 return [ "tag" : "ClampToBorder"]
1147 }
1148 }
1149}
1150extension ImageSemantic {
1151 var toJSON : [String: AnyObject] {
1152 switch self {
1153 case .Depth:
1154 return [ "tag" : "Depth"]
1155 case .Stencil:
1156 return [ "tag" : "Stencil"]
1157 case .Color:
1158 return [ "tag" : "Color"]
1159 }
1160 }
1161}
1162extension ImageRef {
1163 var toJSON : [String: AnyObject] {
1164 switch self {
1165 case .TextureImage(let arg0, let arg1, let arg2):
1166 return [ "tag" : "TextureImage", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON, "arg2" : arg2.toJSON]
1167 case .Framebuffer(let arg0):
1168 return [ "tag" : "Framebuffer", "arg0" : arg0.toJSON]
1169 }
1170 }
1171}
1172extension ClearImage {
1173 var toJSON : [String: AnyObject] {
1174 switch self {
1175 case .ClearImage(let v):
1176 return [ "tag" : "ClearImage"
1177 , "imageSemantic" : v.imageSemantic.toJSON
1178 , "clearValue" : v.clearValue.toJSON
1179 ]
1180 }
1181 }
1182}
1183extension Command {
1184 var toJSON : [String: AnyObject] {
1185 switch self {
1186 case .SetRasterContext(let arg0):
1187 return [ "tag" : "SetRasterContext", "arg0" : arg0.toJSON]
1188 case .SetAccumulationContext(let arg0):
1189 return [ "tag" : "SetAccumulationContext", "arg0" : arg0.toJSON]
1190 case .SetRenderTarget(let arg0):
1191 return [ "tag" : "SetRenderTarget", "arg0" : arg0.toJSON]
1192 case .SetProgram(let arg0):
1193 return [ "tag" : "SetProgram", "arg0" : arg0.toJSON]
1194 case .SetSamplerUniform(let arg0, let arg1):
1195 return [ "tag" : "SetSamplerUniform", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1196 case .SetTexture(let arg0, let arg1):
1197 return [ "tag" : "SetTexture", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1198 case .SetSampler(let arg0, let arg1):
1199 return [ "tag" : "SetSampler", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1200 case .RenderSlot(let arg0):
1201 return [ "tag" : "RenderSlot", "arg0" : arg0.toJSON]
1202 case .RenderStream(let arg0):
1203 return [ "tag" : "RenderStream", "arg0" : arg0.toJSON]
1204 case .ClearRenderTarget(let arg0):
1205 return [ "tag" : "ClearRenderTarget", "arg0" : arg0.toJSON]
1206 case .GenerateMipMap(let arg0):
1207 return [ "tag" : "GenerateMipMap", "arg0" : arg0.toJSON]
1208 case .SaveImage(let arg0, let arg1):
1209 return [ "tag" : "SaveImage", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1210 case .LoadImage(let arg0, let arg1):
1211 return [ "tag" : "LoadImage", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
1212 }
1213 }
1214}
1215extension SamplerDescriptor {
1216 var toJSON : [String: AnyObject] {
1217 switch self {
1218 case .SamplerDescriptor(let v):
1219 return [ "tag" : "SamplerDescriptor"
1220 , "samplerWrapS" : v.samplerWrapS.toJSON
1221 , "samplerWrapT" : v.samplerWrapT.toJSON
1222 , "samplerWrapR" : v.samplerWrapR.toJSON
1223 , "samplerMinFilter" : v.samplerMinFilter.toJSON
1224 , "samplerMagFilter" : v.samplerMagFilter.toJSON
1225 , "samplerBorderColor" : v.samplerBorderColor.toJSON
1226 , "samplerMinLod" : v.samplerMinLod.toJSON
1227 , "samplerMaxLod" : v.samplerMaxLod.toJSON
1228 , "samplerLodBias" : v.samplerLodBias.toJSON
1229 , "samplerCompareFunc" : v.samplerCompareFunc.toJSON
1230 ]
1231 }
1232 }
1233}
1234extension TextureDescriptor {
1235 var toJSON : [String: AnyObject] {
1236 switch self {
1237 case .TextureDescriptor(let v):
1238 return [ "tag" : "TextureDescriptor"
1239 , "textureType" : v.textureType.toJSON
1240 , "textureSize" : v.textureSize.toJSON
1241 , "textureSemantic" : v.textureSemantic.toJSON
1242 , "textureSampler" : v.textureSampler.toJSON
1243 , "textureBaseLevel" : v.textureBaseLevel.toJSON
1244 , "textureMaxLevel" : v.textureMaxLevel.toJSON
1245 ]
1246 }
1247 }
1248}
1249extension Parameter {
1250 var toJSON : [String: AnyObject] {
1251 switch self {
1252 case .Parameter(let v):
1253 return [ "tag" : "Parameter"
1254 , "name" : v.name.toJSON
1255 , "ty" : v.ty.toJSON
1256 ]
1257 }
1258 }
1259}
1260extension Program {
1261 var toJSON : [String: AnyObject] {
1262 switch self {
1263 case .Program(let v):
1264 return [ "tag" : "Program"
1265 , "programUniforms" : v.programUniforms.toJSON
1266 , "programStreams" : v.programStreams.toJSON
1267 , "programInTextures" : v.programInTextures.toJSON
1268 , "programOutput" : v.programOutput.toJSON
1269 , "vertexShader" : v.vertexShader.toJSON
1270 , "geometryShader" : v.geometryShader.toJSON
1271 , "fragmentShader" : v.fragmentShader.toJSON
1272 ]
1273 }
1274 }
1275}
1276extension Slot {
1277 var toJSON : [String: AnyObject] {
1278 switch self {
1279 case .Slot(let v):
1280 return [ "tag" : "Slot"
1281 , "slotName" : v.slotName.toJSON
1282 , "slotStreams" : v.slotStreams.toJSON
1283 , "slotUniforms" : v.slotUniforms.toJSON
1284 , "slotPrimitive" : v.slotPrimitive.toJSON
1285 , "slotPrograms" : v.slotPrograms.toJSON
1286 ]
1287 }
1288 }
1289}
1290extension StreamData {
1291 var toJSON : [String: AnyObject] {
1292 switch self {
1293 case .StreamData(let v):
1294 return [ "tag" : "StreamData"
1295 , "streamData" : v.streamData.toJSON
1296 , "streamType" : v.streamType.toJSON
1297 , "streamPrimitive" : v.streamPrimitive.toJSON
1298 , "streamPrograms" : v.streamPrograms.toJSON
1299 ]
1300 }
1301 }
1302}
1303extension TargetItem {
1304 var toJSON : [String: AnyObject] {
1305 switch self {
1306 case .TargetItem(let v):
1307 return [ "tag" : "TargetItem"
1308 , "targetSemantic" : v.targetSemantic.toJSON
1309 , "targetRef" : v.targetRef.toJSON
1310 ]
1311 }
1312 }
1313}
1314extension RenderTarget {
1315 var toJSON : [String: AnyObject] {
1316 switch self {
1317 case .RenderTarget(let v):
1318 return [ "tag" : "RenderTarget"
1319 , "renderTargets" : v.renderTargets.toJSON
1320 ]
1321 }
1322 }
1323}
1324extension Backend {
1325 var toJSON : [String: AnyObject] {
1326 switch self {
1327 case .WebGL1:
1328 return [ "tag" : "WebGL1"]
1329 case .OpenGL33:
1330 return [ "tag" : "OpenGL33"]
1331 }
1332 }
1333}
1334extension Pipeline {
1335 var toJSON : [String: AnyObject] {
1336 switch self {
1337 case .Pipeline(let v):
1338 return [ "tag" : "Pipeline"
1339 , "backend" : v.backend.toJSON
1340 , "textures" : v.textures.toJSON
1341 , "samplers" : v.samplers.toJSON
1342 , "targets" : v.targets.toJSON
1343 , "programs" : v.programs.toJSON
1344 , "slots" : v.slots.toJSON
1345 , "streams" : v.streams.toJSON
1346 , "commands" : v.commands.toJSON
1347 ]
1348 }
1349 }
1350}
1351
1352enum Maybe<T> {
1353 case Nothing
1354 case Just(T)
1355}
1356
1357enum Type {
1358 case Int
1359 case Int32
1360 case Word
1361 case Word32
1362 case Float
1363 case Bool
1364 case String
1365 case Array(Type)
1366 case List(Type)
1367 case Maybe(Type)
1368 case Map(Type,Type)
1369 case ArrayValue
1370 case Value
1371 case InputType
1372 case PointSpriteCoordOrigin
1373 case PointSize
1374 case PolygonOffset
1375 case FrontFace
1376 case PolygonMode
1377 case ProvokingVertex
1378 case CullMode
1379 case ComparisonFunction
1380 case StencilOperation
1381 case BlendEquation
1382 case BlendingFactor
1383 case LogicOperation
1384 case StencilOps
1385 case StencilTest
1386 case StencilTests
1387 case FetchPrimitive
1388 case OutputPrimitive
1389 case ColorArity
1390 case Blending
1391 case RasterContext
1392 case FragmentOperation
1393 case AccumulationContext
1394 case TextureDataType
1395 case TextureType
1396 case MipMap
1397 case Filter
1398 case EdgeMode
1399 case ImageSemantic
1400 case ImageRef
1401 case ClearImage
1402 case Command
1403 case SamplerDescriptor
1404 case TextureDescriptor
1405 case Parameter
1406 case Program
1407 case Slot
1408 case StreamData
1409 case TargetItem
1410 case RenderTarget
1411 case Backend
1412 case Pipeline
1413}
1414
1415func fromJSON(type: Type, personName: String) -> Any {
1416 switch type {
1417 case .Int: return 0
1418 case .Int32: return 0
1419 case .Word: return 0
1420 case .Word32: return 0
1421 case .Float: return 0.0
1422 case .Bool: return false
1423 case .String: return ""
1424 case .Array(let a): return fromJSON(a,personName)
1425 case .List(let a): return fromJSON(a,personName)
1426 case .Maybe(let a): return fromJSON(a,personName)
1427 }
1428 return 0;
1429} \ No newline at end of file
diff --git a/ddl/out/IR2.hpp b/ddl/out/IR2.hpp
new file mode 100644
index 0000000..61fc2c6
--- /dev/null
+++ b/ddl/out/IR2.hpp
@@ -0,0 +1,1070 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.420877000000Z
3
4#ifndef HEADER_IR_H
5#define HEADER_IR_H
6
7#include "RT.hpp"
8
9
10typedef Int StreamName;
11
12typedef Int ProgramName;
13
14typedef Int TextureName;
15
16typedef Int SamplerName;
17
18typedef String UniformName;
19
20typedef Int SlotName;
21
22typedef Int FrameBufferComponent;
23
24typedef Int TextureUnit;
25
26typedef Int RenderTargetName;
27
28typedef std::map<::UniformName, ::TextureUnit> TextureUnitMapping;
29
30namespace data {
31 class VBoolArray {
32 public:
33 std::vector<Bool> _0;
34 };
35 class VIntArray {
36 public:
37 std::vector<Int32> _0;
38 };
39 class VWordArray {
40 public:
41 std::vector<Word32> _0;
42 };
43 class VFloatArray {
44 public:
45 std::vector<Float> _0;
46 };
47}
48class ArrayValue {
49public:
50 enum class tag {
51 VBoolArray,
52 VIntArray,
53 VWordArray,
54 VFloatArray
55 } tag;
56 std::shared_ptr<data::VBoolArray> VBoolArray;
57 std::shared_ptr<data::VIntArray> VIntArray;
58 std::shared_ptr<data::VWordArray> VWordArray;
59 std::shared_ptr<data::VFloatArray> VFloatArray;
60};
61namespace data {
62 class VBool {
63 public:
64 Bool _0;
65 };
66 class VV2B {
67 public:
68 V2B _0;
69 };
70 class VV3B {
71 public:
72 V3B _0;
73 };
74 class VV4B {
75 public:
76 V4B _0;
77 };
78 class VWord {
79 public:
80 Word32 _0;
81 };
82 class VV2U {
83 public:
84 V2U _0;
85 };
86 class VV3U {
87 public:
88 V3U _0;
89 };
90 class VV4U {
91 public:
92 V4U _0;
93 };
94 class VInt {
95 public:
96 Int32 _0;
97 };
98 class VV2I {
99 public:
100 V2I _0;
101 };
102 class VV3I {
103 public:
104 V3I _0;
105 };
106 class VV4I {
107 public:
108 V4I _0;
109 };
110 class VFloat {
111 public:
112 Float _0;
113 };
114 class VV2F {
115 public:
116 V2F _0;
117 };
118 class VV3F {
119 public:
120 V3F _0;
121 };
122 class VV4F {
123 public:
124 V4F _0;
125 };
126 class VM22F {
127 public:
128 M22F _0;
129 };
130 class VM23F {
131 public:
132 M23F _0;
133 };
134 class VM24F {
135 public:
136 M24F _0;
137 };
138 class VM32F {
139 public:
140 M32F _0;
141 };
142 class VM33F {
143 public:
144 M33F _0;
145 };
146 class VM34F {
147 public:
148 M34F _0;
149 };
150 class VM42F {
151 public:
152 M42F _0;
153 };
154 class VM43F {
155 public:
156 M43F _0;
157 };
158 class VM44F {
159 public:
160 M44F _0;
161 };
162}
163class Value {
164public:
165 enum class tag {
166 VBool,
167 VV2B,
168 VV3B,
169 VV4B,
170 VWord,
171 VV2U,
172 VV3U,
173 VV4U,
174 VInt,
175 VV2I,
176 VV3I,
177 VV4I,
178 VFloat,
179 VV2F,
180 VV3F,
181 VV4F,
182 VM22F,
183 VM23F,
184 VM24F,
185 VM32F,
186 VM33F,
187 VM34F,
188 VM42F,
189 VM43F,
190 VM44F
191 } tag;
192 std::shared_ptr<data::VBool> VBool;
193 std::shared_ptr<data::VV2B> VV2B;
194 std::shared_ptr<data::VV3B> VV3B;
195 std::shared_ptr<data::VV4B> VV4B;
196 std::shared_ptr<data::VWord> VWord;
197 std::shared_ptr<data::VV2U> VV2U;
198 std::shared_ptr<data::VV3U> VV3U;
199 std::shared_ptr<data::VV4U> VV4U;
200 std::shared_ptr<data::VInt> VInt;
201 std::shared_ptr<data::VV2I> VV2I;
202 std::shared_ptr<data::VV3I> VV3I;
203 std::shared_ptr<data::VV4I> VV4I;
204 std::shared_ptr<data::VFloat> VFloat;
205 std::shared_ptr<data::VV2F> VV2F;
206 std::shared_ptr<data::VV3F> VV3F;
207 std::shared_ptr<data::VV4F> VV4F;
208 std::shared_ptr<data::VM22F> VM22F;
209 std::shared_ptr<data::VM23F> VM23F;
210 std::shared_ptr<data::VM24F> VM24F;
211 std::shared_ptr<data::VM32F> VM32F;
212 std::shared_ptr<data::VM33F> VM33F;
213 std::shared_ptr<data::VM34F> VM34F;
214 std::shared_ptr<data::VM42F> VM42F;
215 std::shared_ptr<data::VM43F> VM43F;
216 std::shared_ptr<data::VM44F> VM44F;
217};
218namespace data {
219}
220class InputType {
221public:
222 enum class tag {
223 Bool,
224 V2B,
225 V3B,
226 V4B,
227 Word,
228 V2U,
229 V3U,
230 V4U,
231 Int,
232 V2I,
233 V3I,
234 V4I,
235 Float,
236 V2F,
237 V3F,
238 V4F,
239 M22F,
240 M23F,
241 M24F,
242 M32F,
243 M33F,
244 M34F,
245 M42F,
246 M43F,
247 M44F,
248 STexture1D,
249 STexture2D,
250 STextureCube,
251 STexture1DArray,
252 STexture2DArray,
253 STexture2DRect,
254 FTexture1D,
255 FTexture2D,
256 FTexture3D,
257 FTextureCube,
258 FTexture1DArray,
259 FTexture2DArray,
260 FTexture2DMS,
261 FTexture2DMSArray,
262 FTextureBuffer,
263 FTexture2DRect,
264 ITexture1D,
265 ITexture2D,
266 ITexture3D,
267 ITextureCube,
268 ITexture1DArray,
269 ITexture2DArray,
270 ITexture2DMS,
271 ITexture2DMSArray,
272 ITextureBuffer,
273 ITexture2DRect,
274 UTexture1D,
275 UTexture2D,
276 UTexture3D,
277 UTextureCube,
278 UTexture1DArray,
279 UTexture2DArray,
280 UTexture2DMS,
281 UTexture2DMSArray,
282 UTextureBuffer,
283 UTexture2DRect
284 } tag;
285};
286namespace data {
287}
288class PointSpriteCoordOrigin {
289public:
290 enum class tag {
291 LowerLeft,
292 UpperLeft
293 } tag;
294};
295namespace data {
296 class PointSize {
297 public:
298 Float _0;
299 };
300}
301class PointSize {
302public:
303 enum class tag {
304 PointSize,
305 ProgramPointSize
306 } tag;
307 std::shared_ptr<data::PointSize> PointSize;
308};
309namespace data {
310 class Offset {
311 public:
312 Float _0;
313 Float _1;
314 };
315}
316class PolygonOffset {
317public:
318 enum class tag {
319 NoOffset,
320 Offset
321 } tag;
322 std::shared_ptr<data::Offset> Offset;
323};
324namespace data {
325}
326class FrontFace {
327public:
328 enum class tag {
329 CCW,
330 CW
331 } tag;
332};
333namespace data {
334 class PolygonPoint {
335 public:
336 std::shared_ptr<::PointSize> _0;
337 };
338 class PolygonLine {
339 public:
340 Float _0;
341 };
342}
343class PolygonMode {
344public:
345 enum class tag {
346 PolygonPoint,
347 PolygonLine,
348 PolygonFill
349 } tag;
350 std::shared_ptr<data::PolygonPoint> PolygonPoint;
351 std::shared_ptr<data::PolygonLine> PolygonLine;
352};
353namespace data {
354}
355class ProvokingVertex {
356public:
357 enum class tag {
358 FirstVertex,
359 LastVertex
360 } tag;
361};
362namespace data {
363 class CullFront {
364 public:
365 std::shared_ptr<::FrontFace> _0;
366 };
367 class CullBack {
368 public:
369 std::shared_ptr<::FrontFace> _0;
370 };
371}
372class CullMode {
373public:
374 enum class tag {
375 CullNone,
376 CullFront,
377 CullBack
378 } tag;
379 std::shared_ptr<data::CullFront> CullFront;
380 std::shared_ptr<data::CullBack> CullBack;
381};
382namespace data {
383}
384class ComparisonFunction {
385public:
386 enum class tag {
387 Never,
388 Less,
389 Equal,
390 Lequal,
391 Greater,
392 Notequal,
393 Gequal,
394 Always
395 } tag;
396};
397typedef ComparisonFunction DepthFunction;
398
399namespace data {
400}
401class StencilOperation {
402public:
403 enum class tag {
404 OpZero,
405 OpKeep,
406 OpReplace,
407 OpIncr,
408 OpIncrWrap,
409 OpDecr,
410 OpDecrWrap,
411 OpInvert
412 } tag;
413};
414namespace data {
415}
416class BlendEquation {
417public:
418 enum class tag {
419 FuncAdd,
420 FuncSubtract,
421 FuncReverseSubtract,
422 Min,
423 Max
424 } tag;
425};
426namespace data {
427}
428class BlendingFactor {
429public:
430 enum class tag {
431 Zero,
432 One,
433 SrcColor,
434 OneMinusSrcColor,
435 DstColor,
436 OneMinusDstColor,
437 SrcAlpha,
438 OneMinusSrcAlpha,
439 DstAlpha,
440 OneMinusDstAlpha,
441 ConstantColor,
442 OneMinusConstantColor,
443 ConstantAlpha,
444 OneMinusConstantAlpha,
445 SrcAlphaSaturate
446 } tag;
447};
448namespace data {
449}
450class LogicOperation {
451public:
452 enum class tag {
453 Clear,
454 And,
455 AndReverse,
456 Copy,
457 AndInverted,
458 Noop,
459 Xor,
460 Or,
461 Nor,
462 Equiv,
463 Invert,
464 OrReverse,
465 CopyInverted,
466 OrInverted,
467 Nand,
468 Set
469 } tag;
470};
471namespace data {
472 class StencilOps {
473 public:
474 std::shared_ptr<::StencilOperation> frontStencilOp;
475 std::shared_ptr<::StencilOperation> backStencilOp;
476 };
477}
478class StencilOps {
479public:
480 enum class tag {
481 StencilOps
482 } tag;
483 std::shared_ptr<data::StencilOps> StencilOps;
484};
485namespace data {
486 class StencilTest {
487 public:
488 std::shared_ptr<::ComparisonFunction> stencilComparision;
489 Int32 stencilReference;
490 Word32 stencilMask;
491 };
492}
493class StencilTest {
494public:
495 enum class tag {
496 StencilTest
497 } tag;
498 std::shared_ptr<data::StencilTest> StencilTest;
499};
500namespace data {
501 class StencilTests {
502 public:
503 std::shared_ptr<::StencilTest> _0;
504 std::shared_ptr<::StencilTest> _1;
505 };
506}
507class StencilTests {
508public:
509 enum class tag {
510 StencilTests
511 } tag;
512 std::shared_ptr<data::StencilTests> StencilTests;
513};
514namespace data {
515}
516class FetchPrimitive {
517public:
518 enum class tag {
519 Points,
520 Lines,
521 Triangles,
522 LinesAdjacency,
523 TrianglesAdjacency
524 } tag;
525};
526namespace data {
527}
528class OutputPrimitive {
529public:
530 enum class tag {
531 TrianglesOutput,
532 LinesOutput,
533 PointsOutput
534 } tag;
535};
536namespace data {
537}
538class ColorArity {
539public:
540 enum class tag {
541 Red,
542 RG,
543 RGB,
544 RGBA
545 } tag;
546};
547namespace data {
548 class BlendLogicOp {
549 public:
550 std::shared_ptr<::LogicOperation> _0;
551 };
552 class Blend {
553 public:
554 std::shared_ptr<::BlendEquation> colorEqSrc;
555 std::shared_ptr<::BlendEquation> alphaEqSrc;
556 std::shared_ptr<::BlendingFactor> colorFSrc;
557 std::shared_ptr<::BlendingFactor> colorFDst;
558 std::shared_ptr<::BlendingFactor> alphaFSrc;
559 std::shared_ptr<::BlendingFactor> alphaFDst;
560 V4F color;
561 };
562}
563class Blending {
564public:
565 enum class tag {
566 NoBlending,
567 BlendLogicOp,
568 Blend
569 } tag;
570 std::shared_ptr<data::BlendLogicOp> BlendLogicOp;
571 std::shared_ptr<data::Blend> Blend;
572};
573namespace data {
574 class PointCtx {
575 public:
576 std::shared_ptr<::PointSize> _0;
577 Float _1;
578 std::shared_ptr<::PointSpriteCoordOrigin> _2;
579 };
580 class LineCtx {
581 public:
582 Float _0;
583 std::shared_ptr<::ProvokingVertex> _1;
584 };
585 class TriangleCtx {
586 public:
587 std::shared_ptr<::CullMode> _0;
588 std::shared_ptr<::PolygonMode> _1;
589 std::shared_ptr<::PolygonOffset> _2;
590 std::shared_ptr<::ProvokingVertex> _3;
591 };
592}
593class RasterContext {
594public:
595 enum class tag {
596 PointCtx,
597 LineCtx,
598 TriangleCtx
599 } tag;
600 std::shared_ptr<data::PointCtx> PointCtx;
601 std::shared_ptr<data::LineCtx> LineCtx;
602 std::shared_ptr<data::TriangleCtx> TriangleCtx;
603};
604namespace data {
605 class DepthOp {
606 public:
607 std::shared_ptr<::DepthFunction> _0;
608 Bool _1;
609 };
610 class StencilOp {
611 public:
612 std::shared_ptr<::StencilTests> _0;
613 std::shared_ptr<::StencilOps> _1;
614 std::shared_ptr<::StencilOps> _2;
615 };
616 class ColorOp {
617 public:
618 std::shared_ptr<::Blending> _0;
619 std::shared_ptr<::Value> _1;
620 };
621}
622class FragmentOperation {
623public:
624 enum class tag {
625 DepthOp,
626 StencilOp,
627 ColorOp
628 } tag;
629 std::shared_ptr<data::DepthOp> DepthOp;
630 std::shared_ptr<data::StencilOp> StencilOp;
631 std::shared_ptr<data::ColorOp> ColorOp;
632};
633namespace data {
634 class AccumulationContext {
635 public:
636 Maybe<String> accViewportName;
637 std::vector<std::shared_ptr<::FragmentOperation>> accOperations;
638 };
639}
640class AccumulationContext {
641public:
642 enum class tag {
643 AccumulationContext
644 } tag;
645 std::shared_ptr<data::AccumulationContext> AccumulationContext;
646};
647namespace data {
648 class FloatT {
649 public:
650 std::shared_ptr<::ColorArity> _0;
651 };
652 class IntT {
653 public:
654 std::shared_ptr<::ColorArity> _0;
655 };
656 class WordT {
657 public:
658 std::shared_ptr<::ColorArity> _0;
659 };
660}
661class TextureDataType {
662public:
663 enum class tag {
664 FloatT,
665 IntT,
666 WordT,
667 ShadowT
668 } tag;
669 std::shared_ptr<data::FloatT> FloatT;
670 std::shared_ptr<data::IntT> IntT;
671 std::shared_ptr<data::WordT> WordT;
672};
673namespace data {
674 class Texture1D {
675 public:
676 std::shared_ptr<::TextureDataType> _0;
677 Int _1;
678 };
679 class Texture2D {
680 public:
681 std::shared_ptr<::TextureDataType> _0;
682 Int _1;
683 };
684 class Texture3D {
685 public:
686 std::shared_ptr<::TextureDataType> _0;
687 };
688 class TextureCube {
689 public:
690 std::shared_ptr<::TextureDataType> _0;
691 };
692 class TextureRect {
693 public:
694 std::shared_ptr<::TextureDataType> _0;
695 };
696 class Texture2DMS {
697 public:
698 std::shared_ptr<::TextureDataType> _0;
699 Int _1;
700 Int _2;
701 Bool _3;
702 };
703 class TextureBuffer {
704 public:
705 std::shared_ptr<::TextureDataType> _0;
706 };
707}
708class TextureType {
709public:
710 enum class tag {
711 Texture1D,
712 Texture2D,
713 Texture3D,
714 TextureCube,
715 TextureRect,
716 Texture2DMS,
717 TextureBuffer
718 } tag;
719 std::shared_ptr<data::Texture1D> Texture1D;
720 std::shared_ptr<data::Texture2D> Texture2D;
721 std::shared_ptr<data::Texture3D> Texture3D;
722 std::shared_ptr<data::TextureCube> TextureCube;
723 std::shared_ptr<data::TextureRect> TextureRect;
724 std::shared_ptr<data::Texture2DMS> Texture2DMS;
725 std::shared_ptr<data::TextureBuffer> TextureBuffer;
726};
727namespace data {
728 class Mip {
729 public:
730 Int _0;
731 Int _1;
732 };
733 class AutoMip {
734 public:
735 Int _0;
736 Int _1;
737 };
738}
739class MipMap {
740public:
741 enum class tag {
742 Mip,
743 NoMip,
744 AutoMip
745 } tag;
746 std::shared_ptr<data::Mip> Mip;
747 std::shared_ptr<data::AutoMip> AutoMip;
748};
749namespace data {
750}
751class Filter {
752public:
753 enum class tag {
754 Nearest,
755 Linear,
756 NearestMipmapNearest,
757 NearestMipmapLinear,
758 LinearMipmapNearest,
759 LinearMipmapLinear
760 } tag;
761};
762namespace data {
763}
764class EdgeMode {
765public:
766 enum class tag {
767 Repeat,
768 MirroredRepeat,
769 ClampToEdge,
770 ClampToBorder
771 } tag;
772};
773namespace data {
774}
775class ImageSemantic {
776public:
777 enum class tag {
778 Depth,
779 Stencil,
780 Color
781 } tag;
782};
783namespace data {
784 class TextureImage {
785 public:
786 ::TextureName _0;
787 Int _1;
788 Maybe<Int> _2;
789 };
790 class Framebuffer {
791 public:
792 std::shared_ptr<::ImageSemantic> _0;
793 };
794}
795class ImageRef {
796public:
797 enum class tag {
798 TextureImage,
799 Framebuffer
800 } tag;
801 std::shared_ptr<data::TextureImage> TextureImage;
802 std::shared_ptr<data::Framebuffer> Framebuffer;
803};
804namespace data {
805 class ClearImage {
806 public:
807 std::shared_ptr<::ImageSemantic> imageSemantic;
808 std::shared_ptr<::Value> clearValue;
809 };
810}
811class ClearImage {
812public:
813 enum class tag {
814 ClearImage
815 } tag;
816 std::shared_ptr<data::ClearImage> ClearImage;
817};
818namespace data {
819 class SetRasterContext {
820 public:
821 std::shared_ptr<::RasterContext> _0;
822 };
823 class SetAccumulationContext {
824 public:
825 std::shared_ptr<::AccumulationContext> _0;
826 };
827 class SetRenderTarget {
828 public:
829 ::RenderTargetName _0;
830 };
831 class SetProgram {
832 public:
833 ::ProgramName _0;
834 };
835 class SetSamplerUniform {
836 public:
837 ::UniformName _0;
838 ::TextureUnit _1;
839 };
840 class SetTexture {
841 public:
842 ::TextureUnit _0;
843 ::TextureName _1;
844 };
845 class SetSampler {
846 public:
847 ::TextureUnit _0;
848 Maybe<::SamplerName> _1;
849 };
850 class RenderSlot {
851 public:
852 ::SlotName _0;
853 };
854 class RenderStream {
855 public:
856 ::StreamName _0;
857 };
858 class ClearRenderTarget {
859 public:
860 std::vector<std::shared_ptr<::ClearImage>> _0;
861 };
862 class GenerateMipMap {
863 public:
864 ::TextureUnit _0;
865 };
866 class SaveImage {
867 public:
868 ::FrameBufferComponent _0;
869 std::shared_ptr<::ImageRef> _1;
870 };
871 class LoadImage {
872 public:
873 std::shared_ptr<::ImageRef> _0;
874 ::FrameBufferComponent _1;
875 };
876}
877class Command {
878public:
879 enum class tag {
880 SetRasterContext,
881 SetAccumulationContext,
882 SetRenderTarget,
883 SetProgram,
884 SetSamplerUniform,
885 SetTexture,
886 SetSampler,
887 RenderSlot,
888 RenderStream,
889 ClearRenderTarget,
890 GenerateMipMap,
891 SaveImage,
892 LoadImage
893 } tag;
894 std::shared_ptr<data::SetRasterContext> SetRasterContext;
895 std::shared_ptr<data::SetAccumulationContext> SetAccumulationContext;
896 std::shared_ptr<data::SetRenderTarget> SetRenderTarget;
897 std::shared_ptr<data::SetProgram> SetProgram;
898 std::shared_ptr<data::SetSamplerUniform> SetSamplerUniform;
899 std::shared_ptr<data::SetTexture> SetTexture;
900 std::shared_ptr<data::SetSampler> SetSampler;
901 std::shared_ptr<data::RenderSlot> RenderSlot;
902 std::shared_ptr<data::RenderStream> RenderStream;
903 std::shared_ptr<data::ClearRenderTarget> ClearRenderTarget;
904 std::shared_ptr<data::GenerateMipMap> GenerateMipMap;
905 std::shared_ptr<data::SaveImage> SaveImage;
906 std::shared_ptr<data::LoadImage> LoadImage;
907};
908namespace data {
909 class SamplerDescriptor {
910 public:
911 std::shared_ptr<::EdgeMode> samplerWrapS;
912 Maybe<std::shared_ptr<::EdgeMode>> samplerWrapT;
913 Maybe<std::shared_ptr<::EdgeMode>> samplerWrapR;
914 std::shared_ptr<::Filter> samplerMinFilter;
915 std::shared_ptr<::Filter> samplerMagFilter;
916 std::shared_ptr<::Value> samplerBorderColor;
917 Maybe<Float> samplerMinLod;
918 Maybe<Float> samplerMaxLod;
919 Float samplerLodBias;
920 Maybe<std::shared_ptr<::ComparisonFunction>> samplerCompareFunc;
921 };
922}
923class SamplerDescriptor {
924public:
925 enum class tag {
926 SamplerDescriptor
927 } tag;
928 std::shared_ptr<data::SamplerDescriptor> SamplerDescriptor;
929};
930namespace data {
931 class TextureDescriptor {
932 public:
933 std::shared_ptr<::TextureType> textureType;
934 std::shared_ptr<::Value> textureSize;
935 std::shared_ptr<::ImageSemantic> textureSemantic;
936 std::shared_ptr<::SamplerDescriptor> textureSampler;
937 Int textureBaseLevel;
938 Int textureMaxLevel;
939 };
940}
941class TextureDescriptor {
942public:
943 enum class tag {
944 TextureDescriptor
945 } tag;
946 std::shared_ptr<data::TextureDescriptor> TextureDescriptor;
947};
948namespace data {
949 class Parameter {
950 public:
951 String name;
952 std::shared_ptr<::InputType> ty;
953 };
954}
955class Parameter {
956public:
957 enum class tag {
958 Parameter
959 } tag;
960 std::shared_ptr<data::Parameter> Parameter;
961};
962namespace data {
963 class Program {
964 public:
965 std::map<::UniformName, std::shared_ptr<::InputType>> programUniforms;
966 std::map<::UniformName, std::shared_ptr<::Parameter>> programStreams;
967 std::map<::UniformName, std::shared_ptr<::InputType>> programInTextures;
968 std::vector<std::shared_ptr<::Parameter>> programOutput;
969 String vertexShader;
970 Maybe<String> geometryShader;
971 String fragmentShader;
972 };
973}
974class Program {
975public:
976 enum class tag {
977 Program
978 } tag;
979 std::shared_ptr<data::Program> Program;
980};
981namespace data {
982 class Slot {
983 public:
984 String slotName;
985 std::map<String, std::shared_ptr<::InputType>> slotStreams;
986 std::map<::UniformName, std::shared_ptr<::InputType>> slotUniforms;
987 std::shared_ptr<::FetchPrimitive> slotPrimitive;
988 std::vector<::ProgramName> slotPrograms;
989 };
990}
991class Slot {
992public:
993 enum class tag {
994 Slot
995 } tag;
996 std::shared_ptr<data::Slot> Slot;
997};
998namespace data {
999 class StreamData {
1000 public:
1001 std::map<String, std::shared_ptr<::ArrayValue>> streamData;
1002 std::map<String, std::shared_ptr<::InputType>> streamType;
1003 std::shared_ptr<::FetchPrimitive> streamPrimitive;
1004 std::vector<::ProgramName> streamPrograms;
1005 };
1006}
1007class StreamData {
1008public:
1009 enum class tag {
1010 StreamData
1011 } tag;
1012 std::shared_ptr<data::StreamData> StreamData;
1013};
1014namespace data {
1015 class TargetItem {
1016 public:
1017 std::shared_ptr<::ImageSemantic> targetSemantic;
1018 Maybe<std::shared_ptr<::ImageRef>> targetRef;
1019 };
1020}
1021class TargetItem {
1022public:
1023 enum class tag {
1024 TargetItem
1025 } tag;
1026 std::shared_ptr<data::TargetItem> TargetItem;
1027};
1028namespace data {
1029 class RenderTarget {
1030 public:
1031 std::vector<std::shared_ptr<::TargetItem>> renderTargets;
1032 };
1033}
1034class RenderTarget {
1035public:
1036 enum class tag {
1037 RenderTarget
1038 } tag;
1039 std::shared_ptr<data::RenderTarget> RenderTarget;
1040};
1041namespace data {
1042}
1043class Backend {
1044public:
1045 enum class tag {
1046 WebGL1,
1047 OpenGL33
1048 } tag;
1049};
1050namespace data {
1051 class Pipeline {
1052 public:
1053 std::shared_ptr<::Backend> backend;
1054 std::vector<std::shared_ptr<::TextureDescriptor>> textures;
1055 std::vector<std::shared_ptr<::SamplerDescriptor>> samplers;
1056 std::vector<std::shared_ptr<::RenderTarget>> targets;
1057 std::vector<std::shared_ptr<::Program>> programs;
1058 std::vector<std::shared_ptr<::Slot>> slots;
1059 std::vector<std::shared_ptr<::StreamData>> streams;
1060 std::vector<std::shared_ptr<::Command>> commands;
1061 };
1062}
1063class Pipeline {
1064public:
1065 enum class tag {
1066 Pipeline
1067 } tag;
1068 std::shared_ptr<data::Pipeline> Pipeline;
1069};
1070#endif
diff --git a/ddl/out/Mesh.cpp b/ddl/out/Mesh.cpp
new file mode 100644
index 0000000..1661d8e
--- /dev/null
+++ b/ddl/out/Mesh.cpp
@@ -0,0 +1,228 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.818584000000Z
3
4#include "Mesh.hpp"
5template<> json toJSON<std::shared_ptr<MeshAttribute>>(std::shared_ptr<MeshAttribute> &v) {
6 json obj({});
7 switch (v->tag) {
8 case ::MeshAttribute::tag::A_Float:
9 obj["tag"] = "A_Float";
10 {
11 std::shared_ptr<data::A_Float> tv = std::static_pointer_cast<data::A_Float>(v);
12 obj["arg0"] = toJSON(tv->_0);
13 }
14 break;
15 case ::MeshAttribute::tag::A_V2F:
16 obj["tag"] = "A_V2F";
17 {
18 std::shared_ptr<data::A_V2F> tv = std::static_pointer_cast<data::A_V2F>(v);
19 obj["arg0"] = toJSON(tv->_0);
20 }
21 break;
22 case ::MeshAttribute::tag::A_V3F:
23 obj["tag"] = "A_V3F";
24 {
25 std::shared_ptr<data::A_V3F> tv = std::static_pointer_cast<data::A_V3F>(v);
26 obj["arg0"] = toJSON(tv->_0);
27 }
28 break;
29 case ::MeshAttribute::tag::A_V4F:
30 obj["tag"] = "A_V4F";
31 {
32 std::shared_ptr<data::A_V4F> tv = std::static_pointer_cast<data::A_V4F>(v);
33 obj["arg0"] = toJSON(tv->_0);
34 }
35 break;
36 case ::MeshAttribute::tag::A_M22F:
37 obj["tag"] = "A_M22F";
38 {
39 std::shared_ptr<data::A_M22F> tv = std::static_pointer_cast<data::A_M22F>(v);
40 obj["arg0"] = toJSON(tv->_0);
41 }
42 break;
43 case ::MeshAttribute::tag::A_M33F:
44 obj["tag"] = "A_M33F";
45 {
46 std::shared_ptr<data::A_M33F> tv = std::static_pointer_cast<data::A_M33F>(v);
47 obj["arg0"] = toJSON(tv->_0);
48 }
49 break;
50 case ::MeshAttribute::tag::A_M44F:
51 obj["tag"] = "A_M44F";
52 {
53 std::shared_ptr<data::A_M44F> tv = std::static_pointer_cast<data::A_M44F>(v);
54 obj["arg0"] = toJSON(tv->_0);
55 }
56 break;
57 case ::MeshAttribute::tag::A_Int:
58 obj["tag"] = "A_Int";
59 {
60 std::shared_ptr<data::A_Int> tv = std::static_pointer_cast<data::A_Int>(v);
61 obj["arg0"] = toJSON(tv->_0);
62 }
63 break;
64 case ::MeshAttribute::tag::A_Word:
65 obj["tag"] = "A_Word";
66 {
67 std::shared_ptr<data::A_Word> tv = std::static_pointer_cast<data::A_Word>(v);
68 obj["arg0"] = toJSON(tv->_0);
69 }
70 break;
71 }
72 return obj;
73}
74
75template<> std::shared_ptr<MeshAttribute> fromJSON<std::shared_ptr<MeshAttribute>>(W<std::shared_ptr<MeshAttribute>> v, json &obj) {
76 enum ::MeshAttribute::tag tagType;
77 std::string tag = obj["tag"];
78 if (tag == "A_Float") {
79 tagType = ::MeshAttribute::tag::A_Float;
80 std::shared_ptr<data::A_Float> tv(new data::A_Float());
81 tv->_0 = fromJSON(W<std::vector<Float>>(), obj["arg0"]);
82 return tv;
83 }
84 else if (tag == "A_V2F") {
85 tagType = ::MeshAttribute::tag::A_V2F;
86 std::shared_ptr<data::A_V2F> tv(new data::A_V2F());
87 tv->_0 = fromJSON(W<std::vector<V2F>>(), obj["arg0"]);
88 return tv;
89 }
90 else if (tag == "A_V3F") {
91 tagType = ::MeshAttribute::tag::A_V3F;
92 std::shared_ptr<data::A_V3F> tv(new data::A_V3F());
93 tv->_0 = fromJSON(W<std::vector<V3F>>(), obj["arg0"]);
94 return tv;
95 }
96 else if (tag == "A_V4F") {
97 tagType = ::MeshAttribute::tag::A_V4F;
98 std::shared_ptr<data::A_V4F> tv(new data::A_V4F());
99 tv->_0 = fromJSON(W<std::vector<V4F>>(), obj["arg0"]);
100 return tv;
101 }
102 else if (tag == "A_M22F") {
103 tagType = ::MeshAttribute::tag::A_M22F;
104 std::shared_ptr<data::A_M22F> tv(new data::A_M22F());
105 tv->_0 = fromJSON(W<std::vector<M22F>>(), obj["arg0"]);
106 return tv;
107 }
108 else if (tag == "A_M33F") {
109 tagType = ::MeshAttribute::tag::A_M33F;
110 std::shared_ptr<data::A_M33F> tv(new data::A_M33F());
111 tv->_0 = fromJSON(W<std::vector<M33F>>(), obj["arg0"]);
112 return tv;
113 }
114 else if (tag == "A_M44F") {
115 tagType = ::MeshAttribute::tag::A_M44F;
116 std::shared_ptr<data::A_M44F> tv(new data::A_M44F());
117 tv->_0 = fromJSON(W<std::vector<M44F>>(), obj["arg0"]);
118 return tv;
119 }
120 else if (tag == "A_Int") {
121 tagType = ::MeshAttribute::tag::A_Int;
122 std::shared_ptr<data::A_Int> tv(new data::A_Int());
123 tv->_0 = fromJSON(W<std::vector<Int32>>(), obj["arg0"]);
124 return tv;
125 }
126 else if (tag == "A_Word") {
127 tagType = ::MeshAttribute::tag::A_Word;
128 std::shared_ptr<data::A_Word> tv(new data::A_Word());
129 tv->_0 = fromJSON(W<std::vector<Word32>>(), obj["arg0"]);
130 return tv;
131 }
132 else throw "unknown constructor: " + tag;
133 std::shared_ptr<::MeshAttribute> o(new ::MeshAttribute());
134 o->tag = tagType;
135 return o;
136}
137
138template<> json toJSON<std::shared_ptr<MeshPrimitive>>(std::shared_ptr<MeshPrimitive> &v) {
139 json obj({});
140 switch (v->tag) {
141 case ::MeshPrimitive::tag::P_Points:
142 obj["tag"] = "P_Points";
143 break;
144 case ::MeshPrimitive::tag::P_TriangleStrip:
145 obj["tag"] = "P_TriangleStrip";
146 break;
147 case ::MeshPrimitive::tag::P_Triangles:
148 obj["tag"] = "P_Triangles";
149 break;
150 case ::MeshPrimitive::tag::P_TriangleStripI:
151 obj["tag"] = "P_TriangleStripI";
152 {
153 std::shared_ptr<data::P_TriangleStripI> tv = std::static_pointer_cast<data::P_TriangleStripI>(v);
154 obj["arg0"] = toJSON(tv->_0);
155 }
156 break;
157 case ::MeshPrimitive::tag::P_TrianglesI:
158 obj["tag"] = "P_TrianglesI";
159 {
160 std::shared_ptr<data::P_TrianglesI> tv = std::static_pointer_cast<data::P_TrianglesI>(v);
161 obj["arg0"] = toJSON(tv->_0);
162 }
163 break;
164 }
165 return obj;
166}
167
168template<> std::shared_ptr<MeshPrimitive> fromJSON<std::shared_ptr<MeshPrimitive>>(W<std::shared_ptr<MeshPrimitive>> v, json &obj) {
169 enum ::MeshPrimitive::tag tagType;
170 std::string tag = obj["tag"];
171 if (tag == "P_Points") {
172 tagType = ::MeshPrimitive::tag::P_Points;
173 }
174 else if (tag == "P_TriangleStrip") {
175 tagType = ::MeshPrimitive::tag::P_TriangleStrip;
176 }
177 else if (tag == "P_Triangles") {
178 tagType = ::MeshPrimitive::tag::P_Triangles;
179 }
180 else if (tag == "P_TriangleStripI") {
181 tagType = ::MeshPrimitive::tag::P_TriangleStripI;
182 std::shared_ptr<data::P_TriangleStripI> tv(new data::P_TriangleStripI());
183 tv->_0 = fromJSON(W<std::vector<Int32>>(), obj["arg0"]);
184 return tv;
185 }
186 else if (tag == "P_TrianglesI") {
187 tagType = ::MeshPrimitive::tag::P_TrianglesI;
188 std::shared_ptr<data::P_TrianglesI> tv(new data::P_TrianglesI());
189 tv->_0 = fromJSON(W<std::vector<Int32>>(), obj["arg0"]);
190 return tv;
191 }
192 else throw "unknown constructor: " + tag;
193 std::shared_ptr<::MeshPrimitive> o(new ::MeshPrimitive());
194 o->tag = tagType;
195 return o;
196}
197
198template<> json toJSON<std::shared_ptr<Mesh>>(std::shared_ptr<Mesh> &v) {
199 json obj({});
200 switch (v->tag) {
201 case ::Mesh::tag::Mesh:
202 obj["tag"] = "Mesh";
203 {
204 std::shared_ptr<data::Mesh> tv = std::static_pointer_cast<data::Mesh>(v);
205 obj["mAttributes"] = toJSON(tv->mAttributes);
206 obj["mPrimitive"] = toJSON(tv->mPrimitive);
207 }
208 break;
209 }
210 return obj;
211}
212
213template<> std::shared_ptr<Mesh> fromJSON<std::shared_ptr<Mesh>>(W<std::shared_ptr<Mesh>> v, json &obj) {
214 enum ::Mesh::tag tagType;
215 std::string tag = obj["tag"];
216 if (tag == "Mesh") {
217 tagType = ::Mesh::tag::Mesh;
218 std::shared_ptr<data::Mesh> tv(new data::Mesh());
219 tv->mAttributes = fromJSON(W<std::map<String, std::shared_ptr<::MeshAttribute>>>(), obj["mAttributes"]);
220 tv->mPrimitive = fromJSON(W<std::shared_ptr<::MeshPrimitive>>(), obj["mPrimitive"]);
221 return tv;
222 }
223 else throw "unknown constructor: " + tag;
224 std::shared_ptr<::Mesh> o(new ::Mesh());
225 o->tag = tagType;
226 return o;
227}
228
diff --git a/ddl/out/Mesh.hpp b/ddl/out/Mesh.hpp
new file mode 100644
index 0000000..badf1da
--- /dev/null
+++ b/ddl/out/Mesh.hpp
@@ -0,0 +1,107 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.818584000000Z
3
4#ifndef HEADER_Mesh_H
5#define HEADER_Mesh_H
6
7#include "RT.hpp"
8
9
10class MeshAttribute {
11 public:
12 enum class tag {
13 A_Float,
14 A_V2F,
15 A_V3F,
16 A_V4F,
17 A_M22F,
18 A_M33F,
19 A_M44F,
20 A_Int,
21 A_Word
22 } tag;
23};
24namespace data {
25 class A_Float : public ::MeshAttribute {
26 public:
27 std::vector<Float> _0;
28 A_Float() { tag = tag::A_Float; }
29 };
30 class A_V2F : public ::MeshAttribute {
31 public:
32 std::vector<V2F> _0;
33 A_V2F() { tag = tag::A_V2F; }
34 };
35 class A_V3F : public ::MeshAttribute {
36 public:
37 std::vector<V3F> _0;
38 A_V3F() { tag = tag::A_V3F; }
39 };
40 class A_V4F : public ::MeshAttribute {
41 public:
42 std::vector<V4F> _0;
43 A_V4F() { tag = tag::A_V4F; }
44 };
45 class A_M22F : public ::MeshAttribute {
46 public:
47 std::vector<M22F> _0;
48 A_M22F() { tag = tag::A_M22F; }
49 };
50 class A_M33F : public ::MeshAttribute {
51 public:
52 std::vector<M33F> _0;
53 A_M33F() { tag = tag::A_M33F; }
54 };
55 class A_M44F : public ::MeshAttribute {
56 public:
57 std::vector<M44F> _0;
58 A_M44F() { tag = tag::A_M44F; }
59 };
60 class A_Int : public ::MeshAttribute {
61 public:
62 std::vector<Int32> _0;
63 A_Int() { tag = tag::A_Int; }
64 };
65 class A_Word : public ::MeshAttribute {
66 public:
67 std::vector<Word32> _0;
68 A_Word() { tag = tag::A_Word; }
69 };
70}
71class MeshPrimitive {
72 public:
73 enum class tag {
74 P_Points,
75 P_TriangleStrip,
76 P_Triangles,
77 P_TriangleStripI,
78 P_TrianglesI
79 } tag;
80};
81namespace data {
82 class P_TriangleStripI : public ::MeshPrimitive {
83 public:
84 std::vector<Int32> _0;
85 P_TriangleStripI() { tag = tag::P_TriangleStripI; }
86 };
87 class P_TrianglesI : public ::MeshPrimitive {
88 public:
89 std::vector<Int32> _0;
90 P_TrianglesI() { tag = tag::P_TrianglesI; }
91 };
92}
93class Mesh {
94 public:
95 enum class tag {
96 Mesh
97 } tag;
98};
99namespace data {
100 class Mesh : public ::Mesh {
101 public:
102 std::map<String, std::shared_ptr<::MeshAttribute>> mAttributes;
103 std::shared_ptr<::MeshPrimitive> mPrimitive;
104 Mesh() { tag = tag::Mesh; }
105 };
106}
107#endif
diff --git a/ddl/out/Mesh.hs b/ddl/out/Mesh.hs
new file mode 100644
index 0000000..13a6996
--- /dev/null
+++ b/ddl/out/Mesh.hs
@@ -0,0 +1,114 @@
1-- generated file, do not modify!
2-- 2015-12-21T12:00:19.818584000000Z
3
4{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
5module Mesh where
6
7import Data.Int
8import Data.Word
9import Data.Map
10import Data.Vector (Vector(..))
11import Linear
12
13import Data.Text
14import Data.Aeson hiding (Value,Bool)
15import Data.Aeson.Types hiding (Value,Bool)
16import Control.Monad
17
18
19data MeshAttribute
20 = A_Float (Vector Float)
21 | A_V2F (Vector V2F)
22 | A_V3F (Vector V3F)
23 | A_V4F (Vector V4F)
24 | A_M22F (Vector M22F)
25 | A_M33F (Vector M33F)
26 | A_M44F (Vector M44F)
27 | A_Int (Vector Int32)
28 | A_Word (Vector Word32)
29 deriving (Show, Eq, Ord)
30
31data MeshPrimitive
32 = P_Points
33 | P_TriangleStrip
34 | P_Triangles
35 | P_TriangleStripI (Vector Int32)
36 | P_TrianglesI (Vector Int32)
37 deriving (Show, Eq, Ord)
38
39data Mesh
40 = Mesh
41 { mAttributes :: Map String MeshAttribute
42 , mPrimitive :: MeshPrimitive
43 }
44
45 deriving (Show, Eq, Ord)
46
47
48instance ToJSON MeshAttribute where
49 toJSON v = case v of
50 A_Float arg0 -> object [ "tag" .= ("A_Float" :: Text), "arg0" .= arg0]
51 A_V2F arg0 -> object [ "tag" .= ("A_V2F" :: Text), "arg0" .= arg0]
52 A_V3F arg0 -> object [ "tag" .= ("A_V3F" :: Text), "arg0" .= arg0]
53 A_V4F arg0 -> object [ "tag" .= ("A_V4F" :: Text), "arg0" .= arg0]
54 A_M22F arg0 -> object [ "tag" .= ("A_M22F" :: Text), "arg0" .= arg0]
55 A_M33F arg0 -> object [ "tag" .= ("A_M33F" :: Text), "arg0" .= arg0]
56 A_M44F arg0 -> object [ "tag" .= ("A_M44F" :: Text), "arg0" .= arg0]
57 A_Int arg0 -> object [ "tag" .= ("A_Int" :: Text), "arg0" .= arg0]
58 A_Word arg0 -> object [ "tag" .= ("A_Word" :: Text), "arg0" .= arg0]
59
60instance FromJSON MeshAttribute where
61 parseJSON (Object obj) = do
62 tag <- obj .: "tag"
63 case tag :: Text of
64 "A_Float" -> A_Float <$> obj .: "arg0"
65 "A_V2F" -> A_V2F <$> obj .: "arg0"
66 "A_V3F" -> A_V3F <$> obj .: "arg0"
67 "A_V4F" -> A_V4F <$> obj .: "arg0"
68 "A_M22F" -> A_M22F <$> obj .: "arg0"
69 "A_M33F" -> A_M33F <$> obj .: "arg0"
70 "A_M44F" -> A_M44F <$> obj .: "arg0"
71 "A_Int" -> A_Int <$> obj .: "arg0"
72 "A_Word" -> A_Word <$> obj .: "arg0"
73 parseJSON _ = mzero
74
75instance ToJSON MeshPrimitive where
76 toJSON v = case v of
77 P_Points -> object [ "tag" .= ("P_Points" :: Text)]
78 P_TriangleStrip -> object [ "tag" .= ("P_TriangleStrip" :: Text)]
79 P_Triangles -> object [ "tag" .= ("P_Triangles" :: Text)]
80 P_TriangleStripI arg0 -> object [ "tag" .= ("P_TriangleStripI" :: Text), "arg0" .= arg0]
81 P_TrianglesI arg0 -> object [ "tag" .= ("P_TrianglesI" :: Text), "arg0" .= arg0]
82
83instance FromJSON MeshPrimitive where
84 parseJSON (Object obj) = do
85 tag <- obj .: "tag"
86 case tag :: Text of
87 "P_Points" -> pure P_Points
88 "P_TriangleStrip" -> pure P_TriangleStrip
89 "P_Triangles" -> pure P_Triangles
90 "P_TriangleStripI" -> P_TriangleStripI <$> obj .: "arg0"
91 "P_TrianglesI" -> P_TrianglesI <$> obj .: "arg0"
92 parseJSON _ = mzero
93
94instance ToJSON Mesh where
95 toJSON v = case v of
96 Mesh{..} -> object
97 [ "tag" .= ("Mesh" :: Text)
98 , "mAttributes" .= mAttributes
99 , "mPrimitive" .= mPrimitive
100 ]
101
102instance FromJSON Mesh where
103 parseJSON (Object obj) = do
104 tag <- obj .: "tag"
105 case tag :: Text of
106 "Mesh" -> do
107 mAttributes <- obj .: "mAttributes"
108 mPrimitive <- obj .: "mPrimitive"
109 pure $ Mesh
110 { mAttributes = mAttributes
111 , mPrimitive = mPrimitive
112 }
113 parseJSON _ = mzero
114
diff --git a/ddl/out/Mesh.purs b/ddl/out/Mesh.purs
new file mode 100644
index 0000000..230c896
--- /dev/null
+++ b/ddl/out/Mesh.purs
@@ -0,0 +1,113 @@
1-- generated file, do not modify!
2-- 2015-12-21T12:00:19.818584000000Z
3
4module Mesh 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
20data MeshAttribute
21 = A_Float (Array Float)
22 | A_V2F (Array V2F)
23 | A_V3F (Array V3F)
24 | A_V4F (Array V4F)
25 | A_M22F (Array M22F)
26 | A_M33F (Array M33F)
27 | A_M44F (Array M44F)
28 | A_Int (Array Int32)
29 | A_Word (Array Word32)
30
31data MeshPrimitive
32 = P_Points
33 | P_TriangleStrip
34 | P_Triangles
35 | P_TriangleStripI (Array Int32)
36 | P_TrianglesI (Array Int32)
37
38data Mesh
39 = Mesh
40 { mAttributes :: StrMap MeshAttribute
41 , mPrimitive :: MeshPrimitive
42 }
43
44
45
46
47instance encodeJsonMeshAttribute :: EncodeJson MeshAttribute where
48 encodeJson v = case v of
49 A_Float arg0 -> "tag" := "A_Float" ~> "arg0" := arg0 ~> jsonEmptyObject
50 A_V2F arg0 -> "tag" := "A_V2F" ~> "arg0" := arg0 ~> jsonEmptyObject
51 A_V3F arg0 -> "tag" := "A_V3F" ~> "arg0" := arg0 ~> jsonEmptyObject
52 A_V4F arg0 -> "tag" := "A_V4F" ~> "arg0" := arg0 ~> jsonEmptyObject
53 A_M22F arg0 -> "tag" := "A_M22F" ~> "arg0" := arg0 ~> jsonEmptyObject
54 A_M33F arg0 -> "tag" := "A_M33F" ~> "arg0" := arg0 ~> jsonEmptyObject
55 A_M44F arg0 -> "tag" := "A_M44F" ~> "arg0" := arg0 ~> jsonEmptyObject
56 A_Int arg0 -> "tag" := "A_Int" ~> "arg0" := arg0 ~> jsonEmptyObject
57 A_Word arg0 -> "tag" := "A_Word" ~> "arg0" := arg0 ~> jsonEmptyObject
58
59instance decodeJsonMeshAttribute :: DecodeJson MeshAttribute where
60 decodeJson json = do
61 obj <- decodeJson json
62 tag <- obj .? "tag"
63 case tag of
64 "A_Float" -> A_Float <$> obj .? "arg0"
65 "A_V2F" -> A_V2F <$> obj .? "arg0"
66 "A_V3F" -> A_V3F <$> obj .? "arg0"
67 "A_V4F" -> A_V4F <$> obj .? "arg0"
68 "A_M22F" -> A_M22F <$> obj .? "arg0"
69 "A_M33F" -> A_M33F <$> obj .? "arg0"
70 "A_M44F" -> A_M44F <$> obj .? "arg0"
71 "A_Int" -> A_Int <$> obj .? "arg0"
72 "A_Word" -> A_Word <$> obj .? "arg0"
73
74instance encodeJsonMeshPrimitive :: EncodeJson MeshPrimitive where
75 encodeJson v = case v of
76 P_Points -> "tag" := "P_Points" ~> jsonEmptyObject
77 P_TriangleStrip -> "tag" := "P_TriangleStrip" ~> jsonEmptyObject
78 P_Triangles -> "tag" := "P_Triangles" ~> jsonEmptyObject
79 P_TriangleStripI arg0 -> "tag" := "P_TriangleStripI" ~> "arg0" := arg0 ~> jsonEmptyObject
80 P_TrianglesI arg0 -> "tag" := "P_TrianglesI" ~> "arg0" := arg0 ~> jsonEmptyObject
81
82instance decodeJsonMeshPrimitive :: DecodeJson MeshPrimitive where
83 decodeJson json = do
84 obj <- decodeJson json
85 tag <- obj .? "tag"
86 case tag of
87 "P_Points" -> pure P_Points
88 "P_TriangleStrip" -> pure P_TriangleStrip
89 "P_Triangles" -> pure P_Triangles
90 "P_TriangleStripI" -> P_TriangleStripI <$> obj .? "arg0"
91 "P_TrianglesI" -> P_TrianglesI <$> obj .? "arg0"
92
93instance encodeJsonMesh :: EncodeJson Mesh where
94 encodeJson v = case v of
95 Mesh r ->
96 "tag" := "Mesh" ~>
97 "mAttributes" := r.mAttributes ~>
98 "mPrimitive" := r.mPrimitive ~>
99 jsonEmptyObject
100
101instance decodeJsonMesh :: DecodeJson Mesh where
102 decodeJson json = do
103 obj <- decodeJson json
104 tag <- obj .? "tag"
105 case tag of
106 "Mesh" -> do
107 mAttributes <- obj .? "mAttributes"
108 mPrimitive <- obj .? "mPrimitive"
109 pure $ Mesh
110 { mAttributes:mAttributes
111 , mPrimitive:mPrimitive
112 }
113
diff --git a/ddl/out/Mesh.swift b/ddl/out/Mesh.swift
new file mode 100644
index 0000000..df8ab88
--- /dev/null
+++ b/ddl/out/Mesh.swift
@@ -0,0 +1,174 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.818584000000Z
3
4enum MeshAttribute {
5 case A_Float(Array<Float>)
6 case A_V2F(Array<Int>)
7 case A_V3F(Array<Int>)
8 case A_V4F(Array<Int>)
9 case A_M22F(Array<Int>)
10 case A_M33F(Array<Int>)
11 case A_M44F(Array<Int>)
12 case A_Int(Array<Int32>)
13 case A_Word(Array<UInt32>)
14}
15
16enum MeshPrimitive {
17 case P_Points
18 case P_TriangleStrip
19 case P_Triangles
20 case P_TriangleStripI(Array<Int32>)
21 case P_TrianglesI(Array<Int32>)
22}
23
24enum Mesh {
25 case Mesh(Mesh_Data)
26 struct Mesh_Data {
27 var mAttributes : Dictionary<String, MeshAttribute>
28 var mPrimitive : MeshPrimitive
29 }
30}
31
32
33extension Int {
34 var toJSON : [String: AnyObject] {
35 return ["":""]
36 }
37}
38extension Int32 {
39 var toJSON : [String: AnyObject] {
40 return ["":""]
41 }
42}
43extension UInt {
44 var toJSON : [String: AnyObject] {
45 return ["":""]
46 }
47}
48extension UInt32 {
49 var toJSON : [String: AnyObject] {
50 return ["":""]
51 }
52}
53extension Float {
54 var toJSON : [String: AnyObject] {
55 return ["":""]
56 }
57}
58extension Bool {
59 var toJSON : [String: AnyObject] {
60 return ["":""]
61 }
62}
63extension String {
64 var toJSON : [String: AnyObject] {
65 return ["":""]
66 }
67}
68extension Array {
69 var toJSON : [String: AnyObject] {
70 return ["":""]
71 }
72}
73extension Dictionary {
74 var toJSON : [String: AnyObject] {
75 return ["":""]
76 }
77}
78extension Maybe {
79 var toJSON : [String: AnyObject] {
80 return ["":""]
81 }
82}
83
84
85
86extension MeshAttribute {
87 var toJSON : [String: AnyObject] {
88 switch self {
89 case .A_Float(let arg0):
90 return [ "tag" : "A_Float", "arg0" : arg0.toJSON]
91 case .A_V2F(let arg0):
92 return [ "tag" : "A_V2F", "arg0" : arg0.toJSON]
93 case .A_V3F(let arg0):
94 return [ "tag" : "A_V3F", "arg0" : arg0.toJSON]
95 case .A_V4F(let arg0):
96 return [ "tag" : "A_V4F", "arg0" : arg0.toJSON]
97 case .A_M22F(let arg0):
98 return [ "tag" : "A_M22F", "arg0" : arg0.toJSON]
99 case .A_M33F(let arg0):
100 return [ "tag" : "A_M33F", "arg0" : arg0.toJSON]
101 case .A_M44F(let arg0):
102 return [ "tag" : "A_M44F", "arg0" : arg0.toJSON]
103 case .A_Int(let arg0):
104 return [ "tag" : "A_Int", "arg0" : arg0.toJSON]
105 case .A_Word(let arg0):
106 return [ "tag" : "A_Word", "arg0" : arg0.toJSON]
107 }
108 }
109}
110extension MeshPrimitive {
111 var toJSON : [String: AnyObject] {
112 switch self {
113 case .P_Points:
114 return [ "tag" : "P_Points"]
115 case .P_TriangleStrip:
116 return [ "tag" : "P_TriangleStrip"]
117 case .P_Triangles:
118 return [ "tag" : "P_Triangles"]
119 case .P_TriangleStripI(let arg0):
120 return [ "tag" : "P_TriangleStripI", "arg0" : arg0.toJSON]
121 case .P_TrianglesI(let arg0):
122 return [ "tag" : "P_TrianglesI", "arg0" : arg0.toJSON]
123 }
124 }
125}
126extension Mesh {
127 var toJSON : [String: AnyObject] {
128 switch self {
129 case .Mesh(let v):
130 return [ "tag" : "Mesh"
131 , "mAttributes" : v.mAttributes.toJSON
132 , "mPrimitive" : v.mPrimitive.toJSON
133 ]
134 }
135 }
136}
137
138enum Maybe<T> {
139 case Nothing
140 case Just(T)
141}
142
143enum Type {
144 case Int
145 case Int32
146 case Word
147 case Word32
148 case Float
149 case Bool
150 case String
151 case Array(Type)
152 case List(Type)
153 case Maybe(Type)
154 case Map(Type,Type)
155 case MeshAttribute
156 case MeshPrimitive
157 case Mesh
158}
159
160func fromJSON(type: Type, personName: String) -> Any {
161 switch type {
162 case .Int: return 0
163 case .Int32: return 0
164 case .Word: return 0
165 case .Word32: return 0
166 case .Float: return 0.0
167 case .Bool: return false
168 case .String: return ""
169 case .Array(let a): return fromJSON(a,personName)
170 case .List(let a): return fromJSON(a,personName)
171 case .Maybe(let a): return fromJSON(a,personName)
172 }
173 return 0;
174} \ No newline at end of file
diff --git a/ddl/out/Mesh2.hpp b/ddl/out/Mesh2.hpp
new file mode 100644
index 0000000..aafa637
--- /dev/null
+++ b/ddl/out/Mesh2.hpp
@@ -0,0 +1,107 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.818584000000Z
3
4#ifndef HEADER_Mesh_H
5#define HEADER_Mesh_H
6
7#include "RT.hpp"
8
9
10namespace data {
11 class A_Float {
12 public:
13 std::vector<Float> _0;
14 };
15 class A_V2F {
16 public:
17 std::vector<V2F> _0;
18 };
19 class A_V3F {
20 public:
21 std::vector<V3F> _0;
22 };
23 class A_V4F {
24 public:
25 std::vector<V4F> _0;
26 };
27 class A_M22F {
28 public:
29 std::vector<M22F> _0;
30 };
31 class A_M33F {
32 public:
33 std::vector<M33F> _0;
34 };
35 class A_M44F {
36 public:
37 std::vector<M44F> _0;
38 };
39 class A_Int {
40 public:
41 std::vector<Int32> _0;
42 };
43 class A_Word {
44 public:
45 std::vector<Word32> _0;
46 };
47}
48class MeshAttribute {
49public:
50 enum class tag {
51 A_Float,
52 A_V2F,
53 A_V3F,
54 A_V4F,
55 A_M22F,
56 A_M33F,
57 A_M44F,
58 A_Int,
59 A_Word
60 } tag;
61 std::shared_ptr<data::A_Float> A_Float;
62 std::shared_ptr<data::A_V2F> A_V2F;
63 std::shared_ptr<data::A_V3F> A_V3F;
64 std::shared_ptr<data::A_V4F> A_V4F;
65 std::shared_ptr<data::A_M22F> A_M22F;
66 std::shared_ptr<data::A_M33F> A_M33F;
67 std::shared_ptr<data::A_M44F> A_M44F;
68 std::shared_ptr<data::A_Int> A_Int;
69 std::shared_ptr<data::A_Word> A_Word;
70};
71namespace data {
72 class P_TriangleStripI {
73 public:
74 std::vector<Int32> _0;
75 };
76 class P_TrianglesI {
77 public:
78 std::vector<Int32> _0;
79 };
80}
81class MeshPrimitive {
82public:
83 enum class tag {
84 P_Points,
85 P_TriangleStrip,
86 P_Triangles,
87 P_TriangleStripI,
88 P_TrianglesI
89 } tag;
90 std::shared_ptr<data::P_TriangleStripI> P_TriangleStripI;
91 std::shared_ptr<data::P_TrianglesI> P_TrianglesI;
92};
93namespace data {
94 class Mesh {
95 public:
96 std::map<String, std::shared_ptr<::MeshAttribute>> mAttributes;
97 std::shared_ptr<::MeshPrimitive> mPrimitive;
98 };
99}
100class Mesh {
101public:
102 enum class tag {
103 Mesh
104 } tag;
105 std::shared_ptr<data::Mesh> Mesh;
106};
107#endif
diff --git a/ddl/out/TypeInfo.cpp b/ddl/out/TypeInfo.cpp
new file mode 100644
index 0000000..abf93a5
--- /dev/null
+++ b/ddl/out/TypeInfo.cpp
@@ -0,0 +1,87 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.854088000000Z
3
4#include "TypeInfo.hpp"
5template<> json toJSON<std::shared_ptr<TypeInfo>>(std::shared_ptr<TypeInfo> &v) {
6 json obj({});
7 switch (v->tag) {
8 case ::TypeInfo::tag::TypeInfo:
9 obj["tag"] = "TypeInfo";
10 {
11 std::shared_ptr<data::TypeInfo> tv = std::static_pointer_cast<data::TypeInfo>(v);
12 obj["startLine"] = toJSON(tv->startLine);
13 obj["startColumn"] = toJSON(tv->startColumn);
14 obj["endLine"] = toJSON(tv->endLine);
15 obj["endColumn"] = toJSON(tv->endColumn);
16 obj["text"] = toJSON(tv->text);
17 }
18 break;
19 }
20 return obj;
21}
22
23template<> std::shared_ptr<TypeInfo> fromJSON<std::shared_ptr<TypeInfo>>(W<std::shared_ptr<TypeInfo>> v, json &obj) {
24 enum ::TypeInfo::tag tagType;
25 std::string tag = obj["tag"];
26 if (tag == "TypeInfo") {
27 tagType = ::TypeInfo::tag::TypeInfo;
28 std::shared_ptr<data::TypeInfo> tv(new data::TypeInfo());
29 tv->startLine = fromJSON(W<Int>(), obj["startLine"]);
30 tv->startColumn = fromJSON(W<Int>(), obj["startColumn"]);
31 tv->endLine = fromJSON(W<Int>(), obj["endLine"]);
32 tv->endColumn = fromJSON(W<Int>(), obj["endColumn"]);
33 tv->text = fromJSON(W<String>(), obj["text"]);
34 return tv;
35 }
36 else throw "unknown constructor: " + tag;
37 std::shared_ptr<::TypeInfo> o(new ::TypeInfo());
38 o->tag = tagType;
39 return o;
40}
41
42template<> json toJSON<std::shared_ptr<MyEither>>(std::shared_ptr<MyEither> &v) {
43 json obj({});
44 switch (v->tag) {
45 case ::MyEither::tag::MyLeft:
46 obj["tag"] = "MyLeft";
47 {
48 std::shared_ptr<data::MyLeft> tv = std::static_pointer_cast<data::MyLeft>(v);
49 obj["arg0"] = toJSON(tv->_0);
50 obj["arg1"] = toJSON(tv->_1);
51 }
52 break;
53 case ::MyEither::tag::MyRight:
54 obj["tag"] = "MyRight";
55 {
56 std::shared_ptr<data::MyRight> tv = std::static_pointer_cast<data::MyRight>(v);
57 obj["arg0"] = toJSON(tv->_0);
58 obj["arg1"] = toJSON(tv->_1);
59 }
60 break;
61 }
62 return obj;
63}
64
65template<> std::shared_ptr<MyEither> fromJSON<std::shared_ptr<MyEither>>(W<std::shared_ptr<MyEither>> v, json &obj) {
66 enum ::MyEither::tag tagType;
67 std::string tag = obj["tag"];
68 if (tag == "MyLeft") {
69 tagType = ::MyEither::tag::MyLeft;
70 std::shared_ptr<data::MyLeft> tv(new data::MyLeft());
71 tv->_0 = fromJSON(W<std::shared_ptr<::TypeInfo>>(), obj["arg0"]);
72 tv->_1 = fromJSON(W<std::vector<std::shared_ptr<::TypeInfo>>>(), obj["arg1"]);
73 return tv;
74 }
75 else if (tag == "MyRight") {
76 tagType = ::MyEither::tag::MyRight;
77 std::shared_ptr<data::MyRight> tv(new data::MyRight());
78 tv->_0 = fromJSON(W<std::shared_ptr<::Pipeline>>(), obj["arg0"]);
79 tv->_1 = fromJSON(W<std::vector<std::shared_ptr<::TypeInfo>>>(), obj["arg1"]);
80 return tv;
81 }
82 else throw "unknown constructor: " + tag;
83 std::shared_ptr<::MyEither> o(new ::MyEither());
84 o->tag = tagType;
85 return o;
86}
87
diff --git a/ddl/out/TypeInfo.hpp b/ddl/out/TypeInfo.hpp
new file mode 100644
index 0000000..afba764
--- /dev/null
+++ b/ddl/out/TypeInfo.hpp
@@ -0,0 +1,49 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.854088000000Z
3
4#ifndef HEADER_TypeInfo_H
5#define HEADER_TypeInfo_H
6
7#include "RT.hpp"
8
9#include "IR.hpp"
10
11class TypeInfo {
12 public:
13 enum class tag {
14 TypeInfo
15 } tag;
16};
17namespace data {
18 class TypeInfo : public ::TypeInfo {
19 public:
20 Int startLine;
21 Int startColumn;
22 Int endLine;
23 Int endColumn;
24 String text;
25 TypeInfo() { tag = tag::TypeInfo; }
26 };
27}
28class MyEither {
29 public:
30 enum class tag {
31 MyLeft,
32 MyRight
33 } tag;
34};
35namespace data {
36 class MyLeft : public ::MyEither {
37 public:
38 std::shared_ptr<::TypeInfo> _0;
39 std::vector<std::shared_ptr<::TypeInfo>> _1;
40 MyLeft() { tag = tag::MyLeft; }
41 };
42 class MyRight : public ::MyEither {
43 public:
44 std::shared_ptr<::Pipeline> _0;
45 std::vector<std::shared_ptr<::TypeInfo>> _1;
46 MyRight() { tag = tag::MyRight; }
47 };
48}
49#endif
diff --git a/ddl/out/TypeInfo.hs b/ddl/out/TypeInfo.hs
new file mode 100644
index 0000000..695315f
--- /dev/null
+++ b/ddl/out/TypeInfo.hs
@@ -0,0 +1,79 @@
1-- generated file, do not modify!
2-- 2015-12-21T12:00:19.854088000000Z
3
4{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
5module TypeInfo where
6
7import Data.Int
8import Data.Word
9import Data.Map
10import Data.Vector (Vector(..))
11import Linear
12
13import Data.Text
14import Data.Aeson hiding (Value,Bool)
15import Data.Aeson.Types hiding (Value,Bool)
16import Control.Monad
17
18import IR
19
20data TypeInfo
21 = TypeInfo
22 { startLine :: Int
23 , startColumn :: Int
24 , endLine :: Int
25 , endColumn :: Int
26 , text :: String
27 }
28
29 deriving (Show, Eq, Ord)
30
31data MyEither
32 = MyLeft TypeInfo (Vector TypeInfo)
33 | MyRight Pipeline (Vector TypeInfo)
34 deriving (Show, Eq, Ord)
35
36
37instance ToJSON TypeInfo where
38 toJSON v = case v of
39 TypeInfo{..} -> object
40 [ "tag" .= ("TypeInfo" :: Text)
41 , "startLine" .= startLine
42 , "startColumn" .= startColumn
43 , "endLine" .= endLine
44 , "endColumn" .= endColumn
45 , "text" .= text
46 ]
47
48instance FromJSON TypeInfo where
49 parseJSON (Object obj) = do
50 tag <- obj .: "tag"
51 case tag :: Text of
52 "TypeInfo" -> do
53 startLine <- obj .: "startLine"
54 startColumn <- obj .: "startColumn"
55 endLine <- obj .: "endLine"
56 endColumn <- obj .: "endColumn"
57 text <- obj .: "text"
58 pure $ TypeInfo
59 { startLine = startLine
60 , startColumn = startColumn
61 , endLine = endLine
62 , endColumn = endColumn
63 , text = text
64 }
65 parseJSON _ = mzero
66
67instance ToJSON MyEither where
68 toJSON v = case v of
69 MyLeft arg0 arg1 -> object [ "tag" .= ("MyLeft" :: Text), "arg0" .= arg0, "arg1" .= arg1]
70 MyRight arg0 arg1 -> object [ "tag" .= ("MyRight" :: Text), "arg0" .= arg0, "arg1" .= arg1]
71
72instance FromJSON MyEither where
73 parseJSON (Object obj) = do
74 tag <- obj .: "tag"
75 case tag :: Text of
76 "MyLeft" -> MyLeft <$> obj .: "arg0" <*> obj .: "arg1"
77 "MyRight" -> MyRight <$> obj .: "arg0" <*> obj .: "arg1"
78 parseJSON _ = mzero
79
diff --git a/ddl/out/TypeInfo.purs b/ddl/out/TypeInfo.purs
new file mode 100644
index 0000000..d2d8351
--- /dev/null
+++ b/ddl/out/TypeInfo.purs
@@ -0,0 +1,79 @@
1-- generated file, do not modify!
2-- 2015-12-21T12:00:19.854088000000Z
3
4module TypeInfo 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
19import IR
20
21data TypeInfo
22 = TypeInfo
23 { startLine :: Int
24 , startColumn :: Int
25 , endLine :: Int
26 , endColumn :: Int
27 , text :: String
28 }
29
30
31data MyEither
32 = MyLeft TypeInfo (Array TypeInfo)
33 | MyRight Pipeline (Array TypeInfo)
34
35
36
37instance encodeJsonTypeInfo :: EncodeJson TypeInfo where
38 encodeJson v = case v of
39 TypeInfo r ->
40 "tag" := "TypeInfo" ~>
41 "startLine" := r.startLine ~>
42 "startColumn" := r.startColumn ~>
43 "endLine" := r.endLine ~>
44 "endColumn" := r.endColumn ~>
45 "text" := r.text ~>
46 jsonEmptyObject
47
48instance decodeJsonTypeInfo :: DecodeJson TypeInfo where
49 decodeJson json = do
50 obj <- decodeJson json
51 tag <- obj .? "tag"
52 case tag of
53 "TypeInfo" -> do
54 startLine <- obj .? "startLine"
55 startColumn <- obj .? "startColumn"
56 endLine <- obj .? "endLine"
57 endColumn <- obj .? "endColumn"
58 text <- obj .? "text"
59 pure $ TypeInfo
60 { startLine:startLine
61 , startColumn:startColumn
62 , endLine:endLine
63 , endColumn:endColumn
64 , text:text
65 }
66
67instance encodeJsonMyEither :: EncodeJson MyEither where
68 encodeJson v = case v of
69 MyLeft arg0 arg1 -> "tag" := "MyLeft" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
70 MyRight arg0 arg1 -> "tag" := "MyRight" ~> "arg0" := arg0 ~> "arg1" := arg1 ~> jsonEmptyObject
71
72instance decodeJsonMyEither :: DecodeJson MyEither where
73 decodeJson json = do
74 obj <- decodeJson json
75 tag <- obj .? "tag"
76 case tag of
77 "MyLeft" -> MyLeft <$> obj .? "arg0" <*> obj .? "arg1"
78 "MyRight" -> MyRight <$> obj .? "arg0" <*> obj .? "arg1"
79
diff --git a/ddl/out/TypeInfo.swift b/ddl/out/TypeInfo.swift
new file mode 100644
index 0000000..f05a343
--- /dev/null
+++ b/ddl/out/TypeInfo.swift
@@ -0,0 +1,134 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.854088000000Z
3
4enum TypeInfo {
5 case TypeInfo(TypeInfo_Data)
6 struct TypeInfo_Data {
7 var startLine : Int
8 var startColumn : Int
9 var endLine : Int
10 var endColumn : Int
11 var text : String
12 }
13}
14
15enum MyEither {
16 case MyLeft(TypeInfo,Array<TypeInfo>)
17 case MyRight(Pipeline,Array<TypeInfo>)
18}
19
20
21extension Int {
22 var toJSON : [String: AnyObject] {
23 return ["":""]
24 }
25}
26extension Int32 {
27 var toJSON : [String: AnyObject] {
28 return ["":""]
29 }
30}
31extension UInt {
32 var toJSON : [String: AnyObject] {
33 return ["":""]
34 }
35}
36extension UInt32 {
37 var toJSON : [String: AnyObject] {
38 return ["":""]
39 }
40}
41extension Float {
42 var toJSON : [String: AnyObject] {
43 return ["":""]
44 }
45}
46extension Bool {
47 var toJSON : [String: AnyObject] {
48 return ["":""]
49 }
50}
51extension String {
52 var toJSON : [String: AnyObject] {
53 return ["":""]
54 }
55}
56extension Array {
57 var toJSON : [String: AnyObject] {
58 return ["":""]
59 }
60}
61extension Dictionary {
62 var toJSON : [String: AnyObject] {
63 return ["":""]
64 }
65}
66extension Maybe {
67 var toJSON : [String: AnyObject] {
68 return ["":""]
69 }
70}
71
72
73
74extension TypeInfo {
75 var toJSON : [String: AnyObject] {
76 switch self {
77 case .TypeInfo(let v):
78 return [ "tag" : "TypeInfo"
79 , "startLine" : v.startLine.toJSON
80 , "startColumn" : v.startColumn.toJSON
81 , "endLine" : v.endLine.toJSON
82 , "endColumn" : v.endColumn.toJSON
83 , "text" : v.text.toJSON
84 ]
85 }
86 }
87}
88extension MyEither {
89 var toJSON : [String: AnyObject] {
90 switch self {
91 case .MyLeft(let arg0, let arg1):
92 return [ "tag" : "MyLeft", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
93 case .MyRight(let arg0, let arg1):
94 return [ "tag" : "MyRight", "arg0" : arg0.toJSON, "arg1" : arg1.toJSON]
95 }
96 }
97}
98
99enum Maybe<T> {
100 case Nothing
101 case Just(T)
102}
103
104enum Type {
105 case Int
106 case Int32
107 case Word
108 case Word32
109 case Float
110 case Bool
111 case String
112 case Array(Type)
113 case List(Type)
114 case Maybe(Type)
115 case Map(Type,Type)
116 case TypeInfo
117 case MyEither
118}
119
120func fromJSON(type: Type, personName: String) -> Any {
121 switch type {
122 case .Int: return 0
123 case .Int32: return 0
124 case .Word: return 0
125 case .Word32: return 0
126 case .Float: return 0.0
127 case .Bool: return false
128 case .String: return ""
129 case .Array(let a): return fromJSON(a,personName)
130 case .List(let a): return fromJSON(a,personName)
131 case .Maybe(let a): return fromJSON(a,personName)
132 }
133 return 0;
134} \ No newline at end of file
diff --git a/ddl/out/TypeInfo2.hpp b/ddl/out/TypeInfo2.hpp
new file mode 100644
index 0000000..739db82
--- /dev/null
+++ b/ddl/out/TypeInfo2.hpp
@@ -0,0 +1,49 @@
1// generated file, do not modify!
2// 2015-12-21T12:00:19.854088000000Z
3
4#ifndef HEADER_TypeInfo_H
5#define HEADER_TypeInfo_H
6
7#include "RT.hpp"
8
9#include "IR.hpp"
10
11namespace data {
12 class TypeInfo {
13 public:
14 Int startLine;
15 Int startColumn;
16 Int endLine;
17 Int endColumn;
18 String text;
19 };
20}
21class TypeInfo {
22public:
23 enum class tag {
24 TypeInfo
25 } tag;
26 std::shared_ptr<data::TypeInfo> TypeInfo;
27};
28namespace data {
29 class MyLeft {
30 public:
31 std::shared_ptr<::TypeInfo> _0;
32 std::vector<std::shared_ptr<::TypeInfo>> _1;
33 };
34 class MyRight {
35 public:
36 std::shared_ptr<::Pipeline> _0;
37 std::vector<std::shared_ptr<::TypeInfo>> _1;
38 };
39}
40class MyEither {
41public:
42 enum class tag {
43 MyLeft,
44 MyRight
45 } tag;
46 std::shared_ptr<data::MyLeft> MyLeft;
47 std::shared_ptr<data::MyRight> MyRight;
48};
49#endif
diff --git a/ddl/templates/data.cpp.ede b/ddl/templates/data.cpp.ede
new file mode 100644
index 0000000..39bf39d
--- /dev/null
+++ b/ddl/templates/data.cpp.ede
@@ -0,0 +1,41 @@
1// generated file, do not modify!
2// {{ dateTime }}
3
4#include "{{ moduleName }}.hpp"
5{% for t in definitions %}
6template<> json toJSON<std::shared_ptr<{{ t.value.dataName }}>>(std::shared_ptr<{{ t.value.dataName }}> &v) {
7 json obj({});
8 switch (v->tag) { {% for c in t.value.constructors %}
9 case ::{{ t.value.dataName }}::tag::{{ c.value.name }}:
10 obj["tag"] = "{{ c.value.name }}";{% if !(c.value.fields | empty) %}
11 {
12 std::shared_ptr<data::{{ c.value.name }}> tv = std::static_pointer_cast<data::{{ c.value.name }}>(v);{% for f in c.value.fields %}{% if c.value.fields | hasFieldNames %}
13 obj["{{ f.value.fieldName }}"] = toJSON(tv->{{ f.value.fieldName }});{% else %}
14 obj["arg{{ f.index0 }}"] = toJSON(tv->_{{ f.index0 }});{% endif %}{% endfor %}
15 }{% endif %}
16 break;{% endfor %}
17 }
18 return obj;
19}
20
21template<> std::shared_ptr<{{ t.value.dataName }}> fromJSON<std::shared_ptr<{{ t.value.dataName }}>>(W<std::shared_ptr<{{ t.value.dataName }}>> v, json &obj) {
22 enum ::{{ t.value.dataName }}::tag tagType;
23 std::string tag = obj["tag"];
24 {% for c in t.value.constructors %}
25 {% if !c.first %}else {% endif %}if (tag == "{{ c.value.name }}") {
26 tagType = ::{{ t.value.dataName }}::tag::{{ c.value.name }};
27 {% if !(c.value.fields | empty) %}
28 std::shared_ptr<data::{{ c.value.name }}> tv(new data::{{ c.value.name }}());{% for f in c.value.fields %}{% if c.value.fields | hasFieldNames %}
29 tv->{{ f.value.fieldName }} = fromJSON(W<{{ f.value.fieldType | cppType }}>(), obj["{{ f.value.fieldName }}"]);{% else %}
30 tv->_{{ f.index0 }} = fromJSON(W<{{ f.value.fieldType | cppType }}>(), obj["arg{{ f.index0 }}"]);{% endif %}{% endfor %}
31 return tv;
32 {% endif %}
33 }
34{% endfor %}
35 else throw "unknown constructor: " + tag;
36 std::shared_ptr<::{{ t.value.dataName }}> o(new ::{{ t.value.dataName }}());
37 o->tag = tagType;
38 return o;
39}
40
41{% endfor %}
diff --git a/ddl/templates/data.cs.ede b/ddl/templates/data.cs.ede
new file mode 100644
index 0000000..c88d41c
--- /dev/null
+++ b/ddl/templates/data.cs.ede
@@ -0,0 +1,27 @@
1// generated file, do not modify!
2// {{ dateTime }}
3
4using System.Collections.Generic;
5
6{% for m in imports %}
7using {{ m.value }};
8{% endfor %}
9
10{% for t in dataAndType %}
11{% case t.value | constType %}
12{% when "DataDef" %}
13class {{ t.value.dataName }} {
14 public enum Tag { {% for c in t.value.constructors %}
15 {{ c.value.name }}{% if !c.last %},{% endif %}{% endfor %}
16 };
17 public Tag tag;
18};
19
20namespace data { {% for c in t.value.constructors %}{% if !(c.value.fields | empty) %}
21 class {{ c.value.name }} : global::{{ t.value.dataName }} { {% for f in c.value.fields %}{% if c.value.fields | hasFieldNames %}
22 public {{ f.value.fieldType | csType }} {{ f.value.fieldName }};{% else %}
23 public {{ f.value.fieldType | csType | parens }} _{{ f.index0 }};{% endif %}{% endfor %}
24 };{% endif %}{% endfor %}
25}
26{% endcase %}
27{% endfor %}
diff --git a/ddl/templates/data.hpp.ede b/ddl/templates/data.hpp.ede
new file mode 100644
index 0000000..dab478c
--- /dev/null
+++ b/ddl/templates/data.hpp.ede
@@ -0,0 +1,40 @@
1// generated file, do not modify!
2// {{ dateTime }}
3
4#ifndef HEADER_{{ moduleName }}_H
5#define HEADER_{{ moduleName }}_H
6
7#include "RT.hpp"
8
9{% for m in imports %}
10#include "{{ m.value }}.hpp"
11{% endfor %}
12
13{% for t in dataAndType %}
14{% case t.value | constType %}
15{% when "DataDef" %}
16class {{ t.value.dataName }} {
17 public:
18 enum class tag { {% for c in t.value.constructors %}
19 {{ c.value.name }}{% if !c.last %},{% endif %}{% endfor %}
20 } tag;
21};
22namespace data { {% for c in t.value.constructors %}{% if !(c.value.fields | empty) %}
23 class {{ c.value.name }} : public ::{{ t.value.dataName }} {
24 public:{% for f in c.value.fields %}{% if c.value.fields | hasFieldNames %}
25 {{ f.value.fieldType | cppType }} {{ f.value.fieldName }};{% else %}
26 {{ f.value.fieldType | cppType | parens }} _{{ f.index0 }};{% endif %}{% endfor %}
27 {{ c.value.name }}() { tag = tag::{{ c.value.name }}; }
28 };{% endif %}{% endfor %}
29}
30{% when "TypeAlias" %}
31{% case t.value.aliasType.tag %}
32{% when "Data" %}
33typedef {{ t.value.aliasType.contents }} {{ t.value.aliasName }};
34{% else %}
35typedef {{ t.value.aliasType | cppType }} {{ t.value.aliasName }};
36{% endcase %}
37
38{% endcase %}
39{% endfor %}
40#endif
diff --git a/ddl/templates/data.hpp2.ede b/ddl/templates/data.hpp2.ede
new file mode 100644
index 0000000..b28562d
--- /dev/null
+++ b/ddl/templates/data.hpp2.ede
@@ -0,0 +1,44 @@
1// generated file, do not modify!
2// {{ dateTime }}
3
4#ifndef HEADER_{{ moduleName }}_H
5#define HEADER_{{ moduleName }}_H
6
7#include "RT.hpp"
8
9{% for m in imports %}
10#include "{{ m.value }}.hpp"
11{% endfor %}
12
13{% for t in dataAndType %}
14{% case t.value | constType %}
15{% when "DataDef" %}
16namespace data { {% for c in t.value.constructors %}{% if !(c.value.fields | empty) %}
17 class {{ c.value.name }} {
18 public: {% for f in c.value.fields %}{% if c.value.fields | hasFieldNames %}
19 {{ f.value.fieldType | cppType }} {{ f.value.fieldName }};{% else %}
20 {{ f.value.fieldType | cppType | parens }} _{{ f.index0 }};{% endif %}{% endfor %}
21 };{% endif %}{% endfor %}
22}
23class {{ t.value.dataName }} {
24public:
25 enum class tag { {% for c in t.value.constructors %}
26 {{ c.value.name }}{% if !c.last %},{% endif %}{% endfor %}
27 } tag;
28 {% for c in t.value.constructors %}
29 {% if !(c.value.fields | empty) %}
30 std::shared_ptr<data::{{ c.value.name }}> {{ c.value.name }};
31 {% endif %}
32 {% endfor %}
33};
34{% when "TypeAlias" %}
35{% case t.value.aliasType.tag %}
36{% when "Data" %}
37typedef {{ t.value.aliasType.contents }} {{ t.value.aliasName }};
38{% else %}
39typedef {{ t.value.aliasType | cppType }} {{ t.value.aliasName }};
40{% endcase %}
41
42{% endcase %}
43{% endfor %}
44#endif
diff --git a/ddl/templates/data.hs.ede b/ddl/templates/data.hs.ede
new file mode 100644
index 0000000..54a148b
--- /dev/null
+++ b/ddl/templates/data.hs.ede
@@ -0,0 +1,61 @@
1-- generated file, do not modify!
2-- {{ dateTime }}
3
4{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
5module {{ moduleName }} where
6
7import Data.Int
8import Data.Word
9import Data.Map
10import Data.Vector (Vector(..))
11import Linear
12
13import Data.Text
14import Data.Aeson hiding (Value,Bool)
15import Data.Aeson.Types hiding (Value,Bool)
16import Control.Monad
17
18{% for m in imports %}
19import {{ m.value }}
20{% endfor %}
21
22{% for t in dataAndType %}
23{% case t.value | constType %}
24{% when "DataDef" %}
25data {{ t.value.dataName }}{% for c in t.value.constructors %}
26{% if c.value.fields | hasFieldNames %}
27 {% if c.first %}={% else %}|{% endif %} {{ c.value.name }}
28{% for f in c.value.fields %}{% if f.first %} { {%else%} , {%endif%}{{ f.value.fieldName }} :: {{ f.value.fieldType | hsType }}
29{% endfor %}
30 }
31{% else %}
32 {% if c.first %}={% else %}|{% endif %} {{ c.value.name }}{% for f in c.value.fields %} {{ f.value.fieldType | hsType | parens }}{% endfor %}{% endif %}{% endfor %}
33 deriving (Show, Eq, Ord)
34{% when "TypeAlias" %}
35type {{ t.value.aliasName }} = {{ t.value.aliasType | hsType }}
36{% endcase %}
37
38{% endfor %}
39
40{% for t in definitions %}
41instance ToJSON {{ t.value.dataName }} where
42 toJSON v = case v of{% for c in t.value.constructors %}{% if c.value.fields | hasFieldNames %}
43 {{ c.value.name }}{..} -> object
44 [ "tag" .= ("{{ c.value.name }}" :: Text){% for f in c.value.fields %}
45 , "{{ f.value.fieldName }}" .= {{ f.value.fieldName }}{% endfor %}
46 ]{% else %}
47 {{ c.value.name }}{% for f in c.value.fields %} arg{{ f.index0 }}{% endfor %} -> object [ "tag" .= ("{{ c.value.name }}" :: Text){% for f in c.value.fields %}, "arg{{ f.index0 }}" .= arg{{ f.index0 }}{% endfor %}]{% endif %}{% endfor %}
48
49instance FromJSON {{ t.value.dataName }} where
50 parseJSON (Object obj) = do
51 tag <- obj .: "tag"
52 case tag :: Text of{% for c in t.value.constructors %}{% if c.value.fields | hasFieldNames %}
53 "{{ c.value.name }}" -> do{% for f in c.value.fields %}
54 {{ f.value.fieldName }} <- obj .: "{{ f.value.fieldName }}"{% endfor %}
55 pure $ {{ c.value.name }}{% for f in c.value.fields %}
56 {% if f.first %}{ {% else %}, {%endif%}{{ f.value.fieldName }} = {{ f.value.fieldName }}{% endfor %}
57 } {% else %}
58 "{{ c.value.name }}" -> {% for f in c.value.fields %}{% if f.first %}{{ c.value.name }} <$>{% else %} <*>{% endif %} obj .: "arg{{ f.index0 }}"{%else%}pure {{ c.value.name }}{% endfor %}{% endif %}{% endfor %}
59 parseJSON _ = mzero
60
61{% endfor %} \ No newline at end of file
diff --git a/ddl/templates/data.java.ede b/ddl/templates/data.java.ede
new file mode 100644
index 0000000..c85a521
--- /dev/null
+++ b/ddl/templates/data.java.ede
@@ -0,0 +1,26 @@
1// generated file, do not modify!
2// {{ dateTime }}
3
4{% for m in imports %}
5import {{ m.value }};
6{% endfor %}
7
8public class {{ moduleName }} {
9{% for t in dataAndType %}
10{% case t.value | constType %}
11{% when "DataDef" %}
12 public class {{ t.value.dataName }} {
13 public enum Tag { {% for c in t.value.constructors %}
14 {{ c.value.name }}{% if !c.last %},{% endif %}{% endfor %}
15 }
16 public Tag tag;
17{% for c in t.value.constructors %}{% if !(c.value.fields | empty) %}
18 public class {{ c.value.name }}_ extends {{ t.value.dataName }} { {% for f in c.value.fields %}{% if c.value.fields | hasFieldNames %}
19 public {{ f.value.fieldType | javaType }} {{ f.value.fieldName }};{% else %}
20 public {{ f.value.fieldType | javaType }} _{{ f.index0 }};{% endif %}{% endfor %}
21 }{% endif %}{% endfor %}
22 }
23
24{% endcase %}
25{% endfor %}
26} \ No newline at end of file
diff --git a/ddl/templates/data.purs.ede b/ddl/templates/data.purs.ede
new file mode 100644
index 0000000..0474931
--- /dev/null
+++ b/ddl/templates/data.purs.ede
@@ -0,0 +1,68 @@
1-- generated file, do not modify!
2-- {{ dateTime }}
3
4module {{ moduleName }} 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{% for m in imports %}
20import {{ m.value }}
21{% endfor %}
22
23{% for t in dataAndType %}
24{% case t.value | constType %}
25{% when "DataDef" %}
26data {{ t.value.dataName }}{% for c in t.value.constructors %}
27{% if c.value.fields | hasFieldNames %}
28 {% if c.first %}={% else %}|{% endif %} {{ c.value.name }}
29{% for f in c.value.fields %}{% if f.first %} { {%else%} , {%endif%}{{ f.value.fieldName }} :: {{ f.value.fieldType | psType }}
30{% endfor %}
31 }
32{% else %}
33 {% if c.first %}={% else %}|{% endif %} {{ c.value.name }}{% for f in c.value.fields %} {{ f.value.fieldType | psType | parens }}{% endfor %}{% endif %}{% endfor %}
34
35{% when "TypeAlias" %}
36type {{ t.value.aliasName }} = {{ t.value.aliasType | psType }}
37
38{% endcase %}
39{% endfor %}
40{% for t in definitions %}{% let l = t.value.instances | length %}{% if l > 0 %}{# FIXME!!! #}
41derive instance generic{{ t.value.dataName }} :: Generic {{ t.value.dataName }}
42instance show{{ t.value.dataName }} :: Show {{ t.value.dataName }} where show = gShow
43instance eq{{ t.value.dataName }} :: Eq {{ t.value.dataName }} where eq = gEq
44{% endif %}{% endlet %}{% endfor %}
45
46{# JSON Encode and Decode #}
47{% for t in definitions %}
48instance encodeJson{{ t.value.dataName }} :: EncodeJson {{ t.value.dataName }} where
49 encodeJson v = case v of{% for c in t.value.constructors %}{% if c.value.fields | hasFieldNames %}
50 {{ c.value.name }} r ->
51 "tag" := "{{ c.value.name }}" ~>{% for f in c.value.fields %}
52 "{{ f.value.fieldName }}" := r.{{ f.value.fieldName }} ~>{% endfor %}
53 jsonEmptyObject{% else %}
54 {{ c.value.name }}{% for f in c.value.fields %} arg{{ f.index0 }}{% endfor %} -> "tag" := "{{ c.value.name }}"{% for f in c.value.fields %} ~> "arg{{ f.index0 }}" := arg{{ f.index0 }}{% endfor %} ~> jsonEmptyObject{% endif %}{% endfor %}
55
56instance decodeJson{{ t.value.dataName }} :: DecodeJson {{ t.value.dataName }} where
57 decodeJson json = do
58 obj <- decodeJson json
59 tag <- obj .? "tag"
60 case tag of{% for c in t.value.constructors %}{% if c.value.fields | hasFieldNames %}
61 "{{ c.value.name }}" -> do{% for f in c.value.fields %}
62 {{ f.value.fieldName }} <- obj .? "{{ f.value.fieldName }}"{% endfor %}
63 pure $ {{ c.value.name }}{% for f in c.value.fields %}
64 {% if f.first %}{ {% else %}, {%endif%}{{ f.value.fieldName }}:{{ f.value.fieldName }}{% endfor %}
65 } {% else %}
66 "{{ c.value.name }}" -> {% for f in c.value.fields %}{% if f.first %}{{ c.value.name }} <$>{% else %} <*>{% endif %} obj .? "arg{{ f.index0 }}"{%else%}pure {{ c.value.name }}{% endfor %}{% endif %}{% endfor %}
67
68{% endfor %} \ No newline at end of file
diff --git a/ddl/templates/data.swift.ede b/ddl/templates/data.swift.ede
new file mode 100644
index 0000000..f2a9039
--- /dev/null
+++ b/ddl/templates/data.swift.ede
@@ -0,0 +1,141 @@
1// generated file, do not modify!
2// {{ dateTime }}
3
4{% for t in dataAndType %}
5{% case t.value | constType %}
6{% when "DataDef" %}
7enum {{ t.value.dataName }} {
8{% for c in t.value.constructors %}
9{% if c.value.fields | hasFieldNames %}
10 case {{ c.value.name }}({{ c.value.name }}_Data)
11 struct {{ c.value.name }}_Data {
12{% for f in c.value.fields %}
13 var {{ f.value.fieldName }} : {{ f.value.fieldType | swiftType }}
14{% endfor %}
15 }
16{% else %}
17 case {{ c.value.name }}{% if !(c.value.fields | empty) %}({% for f in c.value.fields %}{{ f.value.fieldType | swiftType }}{% if !f.last %},{% endif %}{% endfor %}){% endif %}
18{% endif %}
19{% endfor %}
20}
21{% when "TypeAlias" %}
22typealias {{ t.value.aliasName }} = {{ t.value.aliasType | swiftType }}
23{% endcase %}
24
25{% endfor %}
26{#
27protocol ToJSON {
28 func toJSON(item: ItemType) -> [String: AnyObject]
29}
30#}
31
32extension Int {
33 var toJSON : [String: AnyObject] {
34 return ["":""]
35 }
36}
37extension Int32 {
38 var toJSON : [String: AnyObject] {
39 return ["":""]
40 }
41}
42extension UInt {
43 var toJSON : [String: AnyObject] {
44 return ["":""]
45 }
46}
47extension UInt32 {
48 var toJSON : [String: AnyObject] {
49 return ["":""]
50 }
51}
52extension Float {
53 var toJSON : [String: AnyObject] {
54 return ["":""]
55 }
56}
57extension Bool {
58 var toJSON : [String: AnyObject] {
59 return ["":""]
60 }
61}
62extension String {
63 var toJSON : [String: AnyObject] {
64 return ["":""]
65 }
66}
67extension Array {
68 var toJSON : [String: AnyObject] {
69 return ["":""]
70 }
71}
72extension Dictionary {
73 var toJSON : [String: AnyObject] {
74 return ["":""]
75 }
76}
77extension Maybe {
78 var toJSON : [String: AnyObject] {
79 return ["":""]
80 }
81}
82
83
84
85{% for t in definitions %}
86extension {{ t.value.dataName }} {
87 var toJSON : [String: AnyObject] {
88 switch self {
89{% for c in t.value.constructors %}
90{% if c.value.fields | hasFieldNames %}
91 case .{{ c.value.name }}(let v):
92 return [ "tag" : "{{ c.value.name }}"{% for f in c.value.fields %}
93 , "{{ f.value.fieldName }}" : v.{{ f.value.fieldName }}.toJSON{% endfor %}
94 ]
95{% else %}
96 case .{{ c.value.name }}{% if !(c.value.fields | empty) %}({% for f in c.value.fields %}let arg{{ f.index0 }}{% if !f.last %}, {% endif %}{% endfor %}){% endif %}:
97 return [ "tag" : "{{ c.value.name }}"{% for f in c.value.fields %}, "arg{{ f.index0 }}" : arg{{ f.index0 }}.toJSON{% endfor %}]
98{% endif %}
99{% endfor %}
100 }
101 }
102}
103{% endfor %}
104
105enum Maybe<T> {
106 case Nothing
107 case Just(T)
108}
109
110enum Type {
111 case Int
112 case Int32
113 case Word
114 case Word32
115 case Float
116 case Bool
117 case String
118 case Array(Type)
119 case List(Type)
120 case Maybe(Type)
121 case Map(Type,Type)
122{% for t in definitions %}
123 case {{ t.value.dataName }}
124{% endfor %}
125}
126
127func fromJSON(type: Type, personName: String) -> Any {
128 switch type {
129 case .Int: return 0
130 case .Int32: return 0
131 case .Word: return 0
132 case .Word32: return 0
133 case .Float: return 0.0
134 case .Bool: return false
135 case .String: return ""
136 case .Array(let a): return fromJSON(a,personName)
137 case .List(let a): return fromJSON(a,personName)
138 case .Maybe(let a): return fromJSON(a,personName)
139 }
140 return 0;
141} \ No newline at end of file
diff --git a/ddl/test/idCpp.cpp b/ddl/test/idCpp.cpp
new file mode 100644
index 0000000..24894f4
--- /dev/null
+++ b/ddl/test/idCpp.cpp
@@ -0,0 +1,31 @@
1#include <string>
2#include <iostream>
3#include <istream>
4#include <ostream>
5#include <iterator>
6
7#include "Mesh.hpp"
8#include "IR.hpp"
9#include "TypeInfo.hpp"
10
11int main() {
12 // don't skip the whitespace while reading
13 std::cin >> std::noskipws;
14
15 // use stream iterators to copy the stream to a string
16 std::istream_iterator<char> it(std::cin);
17 std::istream_iterator<char> end;
18 std::string results(it, end);
19
20 try {
21 json jobjIn = json::parse(results);
22 std::shared_ptr<Pipeline> b = fromJSON(W<std::shared_ptr<Pipeline>>(),jobjIn);
23 std::shared_ptr<data::Pipeline> tv = std::static_pointer_cast<data::Pipeline>(b);
24 json jobjOut = toJSON(b);
25 std::cout << jobjOut;
26 } catch (std::string e) {
27 std::cout << "exception: " << e << "\n";
28 } catch (...) { std::cout << "default exception\n"; }
29
30 return 0;
31}
diff --git a/ddl/test/idHs.hs b/ddl/test/idHs.hs
new file mode 100644
index 0000000..7cd9917
--- /dev/null
+++ b/ddl/test/idHs.hs
@@ -0,0 +1,8 @@
1{-# LANGUAGE ScopedTypeVariables #-}
2import qualified Data.ByteString.Lazy as B
3import Data.Aeson
4import IR
5
6main = do
7 Just (p :: Pipeline) <- decode <$> B.getContents
8 B.putStr $ encode p