{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Glsl (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "GLSL" , sFilename = "glsl.xml" , sShortname = "Glsl" , sContexts = fromList [ ( "Commentar 1" , Context { cName = "Commentar 1" , cSyntax = "GLSL" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "BUG" , "FIXME" , "TODO" ]) , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Commentar 2" , Context { cName = "Commentar 2" , cSyntax = "GLSL" , cRules = [ Rule { rMatcher = Detect2Chars '*' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "BUG" , "FIXME" , "TODO" ]) , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Member" , Context { cName = "Member" , cSyntax = "GLSL" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\b[_\\w][_\\w\\d]*(?=[\\s]*)" , reCompiled = Just (compileRegex True "\\b[_\\w][_\\w\\d]*(?=[\\s]*)") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = True , cFallthroughContext = [ Pop ] , cDynamic = False } ) , ( "Normal" , Context { cName = "Normal" , cSyntax = "GLSL" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "break" , "buffer" , "continue" , "discard" , "do" , "else" , "false" , "for" , "if" , "invariant" , "layout" , "return" , "struct" , "subroutine" , "true" , "uniform" , "while" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "atomic_uint" , "bool" , "bvec2" , "bvec3" , "bvec4" , "float" , "int" , "isampler1D" , "isampler1DArray" , "isampler1DArrayShadow" , "isampler1DShadow" , "isampler2D" , "isampler2DArray" , "isampler2DArrayShadow" , "isampler2DMS" , "isampler2DMSArray" , "isampler2DRect" , "isampler2DRectShadow" , "isampler2DShadow" , "isampler3D" , "isamplerBuffer" , "isamplerCube" , "isamplerCubeArray" , "isamplerCubeArrayShadow" , "isamplerCubeShadow" , "ivec2" , "ivec3" , "ivec4" , "mat2" , "mat3" , "mat4" , "sampler1D" , "sampler1DArray" , "sampler1DArrayShadow" , "sampler1DShadow" , "sampler2D" , "sampler2DArray" , "sampler2DArrayShadow" , "sampler2DMS" , "sampler2DMSArray" , "sampler2DRect" , "sampler2DRectShadow" , "sampler2DShadow" , "sampler3D" , "samplerBuffer" , "samplerCube" , "samplerCubeArray" , "samplerCubeArrayShadow" , "samplerCubeShadow" , "usampler1D" , "usampler1DArray" , "usampler1DArrayShadow" , "usampler1DShadow" , "usampler2D" , "usampler2DArray" , "usampler2DArrayShadow" , "usampler2DMS" , "usampler2DMSArray" , "usampler2DRect" , "usampler2DRectShadow" , "usampler2DShadow" , "usampler3D" , "usamplerBuffer" , "usamplerCube" , "usamplerCubeArray" , "usamplerCubeArrayShadow" , "usamplerCubeShadow" , "vec2" , "vec3" , "vec4" , "void" ]) , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "attribute" , "binding" , "ccw" , "coherent" , "component" , "const" , "cw" , "early_fragment_tests" , "equal_spacing" , "flat" , "fractional_even_spacing" , "fractional_odd_spacing" , "in" , "index" , "inout" , "invocations" , "isolines" , "line_strip" , "lines" , "lines_adjacency" , "location" , "max_vertices" , "noperspective" , "offset" , "origin_upper_left" , "out" , "packed" , "pixel_center_integer" , "point_mode" , "points" , "quads" , "readonly" , "restrict" , "row_major" , "shared" , "smooth" , "std140" , "std430" , "stream" , "triangle_strip" , "triangles" , "triangles_adjacency" , "varying" , "vertices" , "volatile" , "writeonly" , "xfb_buffer" , "xfb_offset" , "xfb_stride" ]) , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "EmitStreamVertex" , "EmitVertex" , "EndPrimitive" , "EndStreamPrimitive" , "abs" , "acos" , "acosh" , "all" , "any" , "asin" , "asinh" , "atan" , "atanh" , "atomicAdd" , "atomicAnd" , "atomicCompSwap" , "atomicCounter" , "atomicCounterDecrement" , "atomicCounterIncrement" , "atomicExchange" , "atomicMax" , "atomicMin" , "atomicOr" , "atomicXor" , "barrier" , "bitCount" , "bitfieldExtract" , "bitfieldInsert" , "bitfieldReverse" , "ceil" , "clamp" , "cos" , "cosh" , "cross" , "dFdx" , "dFdxCoarse" , "dFdxFine" , "dFdy" , "dFdyCoarse" , "dFdyFine" , "degrees" , "determinant" , "distance" , "dot" , "equal" , "exp" , "exp2" , "faceforward" , "findLSB" , "findMSB" , "floatBitsToInt" , "floatBitsToUint" , "floor" , "fma" , "fract" , "frexp" , "fwidth" , "fwidthCoarse" , "fwidthFine" , "glActiveShaderProgram" , "glActiveTexture" , "glAttachShader" , "glBeginConditionalRender" , "glBeginQuery" , "glBeginQueryIndexed" , "glBeginTransformFeedback" , "glBindAttribLocation" , "glBindBuffer" , "glBindBufferBase" , "glBindBufferRange" , "glBindBuffersBase" , "glBindBuffersRange" , "glBindFragDataLocation" , "glBindFragDataLocationIndexed" , "glBindFramebuffer" , "glBindImageTexture" , "glBindImageTextures" , "glBindProgramPipeline" , "glBindRenderbuffer" , "glBindSampler" , "glBindSamplers" , "glBindTexture" , "glBindTextureUnit" , "glBindTextures" , "glBindTransformFeedback" , "glBindVertexArray" , "glBindVertexBuffer" , "glBindVertexBuffers" , "glBlendColor" , "glBlendEquation" , "glBlendEquationSeparate" , "glBlendEquationSeparatei" , "glBlendEquationi" , "glBlendFunc" , "glBlendFuncSeparate" , "glBlendFuncSeparatei" , "glBlendFunci" , "glBlitFramebuffer" , "glBlitNamedFramebuffer" , "glBufferData" , "glBufferStorage" , "glBufferSubData" , "glCheckFramebufferStatus" , "glCheckNamedFramebufferStatus" , "glClampColor" , "glClear" , "glClearBuffer" , "glClearBufferData" , "glClearBufferSubData" , "glClearBufferfi" , "glClearBufferfv" , "glClearBufferiv" , "glClearBufferuiv" , "glClearColor" , "glClearDepth" , "glClearDepthf" , "glClearNamedBufferData" , "glClearNamedBufferSubData" , "glClearNamedFramebufferfi" , "glClearNamedFramebufferfv" , "glClearNamedFramebufferiv" , "glClearNamedFramebufferuiv" , "glClearStencil" , "glClearTexImage" , "glClearTexSubImage" , "glClientWaitSync" , "glClipControl" , "glColorMask" , "glColorMaski" , "glCompileShader" , "glCompressedTexImage1D" , "glCompressedTexImage2D" , "glCompressedTexImage3D" , "glCompressedTexSubImage1D" , "glCompressedTexSubImage2D" , "glCompressedTexSubImage3D" , "glCompressedTextureSubImage1D" , "glCompressedTextureSubImage2D" , "glCompressedTextureSubImage3D" , "glCopyBufferSubData" , "glCopyImageSubData" , "glCopyNamedBufferSubData" , "glCopyTexImage1D" , "glCopyTexImage2D" , "glCopyTexSubImage1D" , "glCopyTexSubImage2D" , "glCopyTexSubImage3D" , "glCopyTextureSubImage1D" , "glCopyTextureSubImage2D" , "glCopyTextureSubImage3D" , "glCreateBuffers" , "glCreateFramebuffers" , "glCreateProgram" , "glCreateProgramPipelines" , "glCreateQueries" , "glCreateRenderbuffers" , "glCreateSamplers" , "glCreateShader" , "glCreateShaderProgram" , "glCreateShaderProgramv" , "glCreateTextures" , "glCreateTransformFeedbacks" , "glCreateVertexArrays" , "glCullFace" , "glDebugMessageCallback" , "glDebugMessageControl" , "glDebugMessageInsert" , "glDeleteBuffers" , "glDeleteFramebuffers" , "glDeleteProgram" , "glDeleteProgramPipelines" , "glDeleteQueries" , "glDeleteRenderbuffers" , "glDeleteSamplers" , "glDeleteShader" , "glDeleteSync" , "glDeleteTextures" , "glDeleteTransformFeedbacks" , "glDeleteVertexArrays" , "glDepthFunc" , "glDepthMask" , "glDepthRange" , "glDepthRangeArray" , "glDepthRangeArrayv" , "glDepthRangeIndexed" , "glDepthRangef" , "glDetachShader" , "glDisable" , "glDisableVertexArrayAttrib" , "glDisableVertexAttribArray" , "glDisablei" , "glDispatchCompute" , "glDispatchComputeIndirect" , "glDrawArrays" , "glDrawArraysIndirect" , "glDrawArraysInstanced" , "glDrawArraysInstancedBaseInstance" , "glDrawBuffer" , "glDrawBuffers" , "glDrawElements" , "glDrawElementsBaseVertex" , "glDrawElementsIndirect" , "glDrawElementsInstanced" , "glDrawElementsInstancedBaseInstance" , "glDrawElementsInstancedBaseVertex" , "glDrawElementsInstancedBaseVertexBaseInstance" , "glDrawRangeElements" , "glDrawRangeElementsBaseVertex" , "glDrawTransformFeedback" , "glDrawTransformFeedbackInstanced" , "glDrawTransformFeedbackStream" , "glDrawTransformFeedbackStreamInstanced" , "glEnable" , "glEnableVertexArrayAttrib" , "glEnableVertexAttribArray" , "glEnablei" , "glEndConditionalRender" , "glEndQuery" , "glEndQueryIndexed" , "glEndTransformFeedback" , "glFenceSync" , "glFinish" , "glFlush" , "glFlushMappedBufferRange" , "glFlushMappedNamedBufferRange" , "glFramebufferParameteri" , "glFramebufferRenderbuffer" , "glFramebufferTexture" , "glFramebufferTexture1D" , "glFramebufferTexture2D" , "glFramebufferTexture3D" , "glFramebufferTextureLayer" , "glFrontFace" , "glGenBuffers" , "glGenFramebuffers" , "glGenProgramPipelines" , "glGenQueries" , "glGenRenderbuffers" , "glGenSamplers" , "glGenTextures" , "glGenTransformFeedbacks" , "glGenVertexArrays" , "glGenerateMipmap" , "glGenerateTextureMipmap" , "glGet" , "glGetActiveAtomicCounterBufferiv" , "glGetActiveAttrib" , "glGetActiveSubroutineName" , "glGetActiveSubroutineUniform" , "glGetActiveSubroutineUniformName" , "glGetActiveSubroutineUniformiv" , "glGetActiveUniform" , "glGetActiveUniformBlock" , "glGetActiveUniformBlockName" , "glGetActiveUniformBlockiv" , "glGetActiveUniformName" , "glGetActiveUniformsiv" , "glGetAttachedShaders" , "glGetAttribLocation" , "glGetBooleani_v" , "glGetBooleanv" , "glGetBufferParameter" , "glGetBufferParameteri64v" , "glGetBufferParameteriv" , "glGetBufferPointerv" , "glGetBufferSubData" , "glGetCompressedTexImage" , "glGetCompressedTextureImage" , "glGetCompressedTextureSubImage" , "glGetDebugMessageLog" , "glGetDoublei_v" , "glGetDoublev" , "glGetError" , "glGetFloati_v" , "glGetFloatv" , "glGetFragDataIndex" , "glGetFragDataLocation" , "glGetFramebufferAttachmentParameter" , "glGetFramebufferAttachmentParameteriv" , "glGetFramebufferParameter" , "glGetFramebufferParameteriv" , "glGetGraphicsResetStatus" , "glGetInteger64i_v" , "glGetInteger64v" , "glGetIntegeri_v" , "glGetIntegerv" , "glGetInternalformat" , "glGetInternalformati64v" , "glGetInternalformativ" , "glGetMultisample" , "glGetMultisamplefv" , "glGetNamedBufferParameteri64v" , "glGetNamedBufferParameteriv" , "glGetNamedBufferPointerv" , "glGetNamedBufferSubData" , "glGetNamedFramebufferAttachmentParameteriv" , "glGetNamedFramebufferParameteriv" , "glGetNamedRenderbufferParameteriv" , "glGetObjectLabel" , "glGetObjectPtrLabel" , "glGetPointerv" , "glGetProgram" , "glGetProgramBinary" , "glGetProgramInfoLog" , "glGetProgramInterface" , "glGetProgramInterfaceiv" , "glGetProgramPipeline" , "glGetProgramPipelineInfoLog" , "glGetProgramPipelineiv" , "glGetProgramResource" , "glGetProgramResourceIndex" , "glGetProgramResourceLocation" , "glGetProgramResourceLocationIndex" , "glGetProgramResourceName" , "glGetProgramResourceiv" , "glGetProgramStage" , "glGetProgramStageiv" , "glGetProgramiv" , "glGetQueryIndexed" , "glGetQueryIndexediv" , "glGetQueryObject" , "glGetQueryObjecti64v" , "glGetQueryObjectiv" , "glGetQueryObjectui64v" , "glGetQueryObjectuiv" , "glGetQueryiv" , "glGetRenderbufferParameter" , "glGetRenderbufferParameteriv" , "glGetSamplerParameter" , "glGetSamplerParameterIiv" , "glGetSamplerParameterIuiv" , "glGetSamplerParameterfv" , "glGetSamplerParameteriv" , "glGetShader" , "glGetShaderInfoLog" , "glGetShaderPrecisionFormat" , "glGetShaderSource" , "glGetShaderiv" , "glGetString" , "glGetStringi" , "glGetSubroutineIndex" , "glGetSubroutineUniformLocation" , "glGetSync" , "glGetSynciv" , "glGetTexImage" , "glGetTexLevelParameter" , "glGetTexLevelParameterfv" , "glGetTexLevelParameteriv" , "glGetTexParameter" , "glGetTexParameterIiv" , "glGetTexParameterIuiv" , "glGetTexParameterfv" , "glGetTexParameteriv" , "glGetTextureImage" , "glGetTextureLevelParameterfv" , "glGetTextureLevelParameteriv" , "glGetTextureParameterIiv" , "glGetTextureParameterIuiv" , "glGetTextureParameterfv" , "glGetTextureParameteriv" , "glGetTextureSubImage" , "glGetTransformFeedback" , "glGetTransformFeedbackVarying" , "glGetTransformFeedbacki64_v" , "glGetTransformFeedbacki_v" , "glGetTransformFeedbackiv" , "glGetUniform" , "glGetUniformBlockIndex" , "glGetUniformIndices" , "glGetUniformLocation" , "glGetUniformSubroutine" , "glGetUniformSubroutineuiv" , "glGetUniformdv" , "glGetUniformfv" , "glGetUniformiv" , "glGetUniformuiv" , "glGetVertexArrayIndexed" , "glGetVertexArrayIndexed64iv" , "glGetVertexArrayIndexediv" , "glGetVertexArrayiv" , "glGetVertexAttrib" , "glGetVertexAttribIiv" , "glGetVertexAttribIuiv" , "glGetVertexAttribLdv" , "glGetVertexAttribPointerv" , "glGetVertexAttribdv" , "glGetVertexAttribfv" , "glGetVertexAttribiv" , "glGetnCompressedTexImage" , "glGetnTexImage" , "glGetnUniformdv" , "glGetnUniformfv" , "glGetnUniformiv" , "glGetnUniformuiv" , "glHint" , "glInvalidateBufferData" , "glInvalidateBufferSubData" , "glInvalidateFramebuffer" , "glInvalidateNamedFramebufferData" , "glInvalidateNamedFramebufferSubData" , "glInvalidateSubFramebuffer" , "glInvalidateTexImage" , "glInvalidateTexSubImage" , "glIsBuffer" , "glIsEnabled" , "glIsEnabledi" , "glIsFramebuffer" , "glIsProgram" , "glIsProgramPipeline" , "glIsQuery" , "glIsRenderbuffer" , "glIsSampler" , "glIsShader" , "glIsSync" , "glIsTexture" , "glIsTransformFeedback" , "glIsVertexArray" , "glLineWidth" , "glLinkProgram" , "glLogicOp" , "glMapBuffer" , "glMapBufferRange" , "glMapNamedBuffer" , "glMapNamedBufferRange" , "glMemoryBarrier" , "glMemoryBarrierByRegion" , "glMinSampleShading" , "glMultiDrawArrays" , "glMultiDrawArraysIndirect" , "glMultiDrawElements" , "glMultiDrawElementsBaseVertex" , "glMultiDrawElementsIndirect" , "glNamedBufferData" , "glNamedBufferStorage" , "glNamedBufferSubData" , "glNamedFramebufferDrawBuffer" , "glNamedFramebufferDrawBuffers" , "glNamedFramebufferParameteri" , "glNamedFramebufferReadBuffer" , "glNamedFramebufferRenderbuffer" , "glNamedFramebufferTexture" , "glNamedFramebufferTextureLayer" , "glNamedRenderbufferStorage" , "glNamedRenderbufferStorageMultisample" , "glObjectLabel" , "glObjectPtrLabel" , "glPatchParameter" , "glPatchParameterfv" , "glPatchParameteri" , "glPauseTransformFeedback" , "glPixelStore" , "glPixelStoref" , "glPixelStorei" , "glPointParameter" , "glPointParameterf" , "glPointParameterfv" , "glPointParameteri" , "glPointParameteriv" , "glPointSize" , "glPolygonMode" , "glPolygonOffset" , "glPopDebugGroup" , "glPrimitiveRestartIndex" , "glProgramBinary" , "glProgramParameter" , "glProgramParameteri" , "glProgramUniform" , "glProgramUniform1f" , "glProgramUniform1fv" , "glProgramUniform1i" , "glProgramUniform1iv" , "glProgramUniform1ui" , "glProgramUniform1uiv" , "glProgramUniform2f" , "glProgramUniform2fv" , "glProgramUniform2i" , "glProgramUniform2iv" , "glProgramUniform2ui" , "glProgramUniform2uiv" , "glProgramUniform3f" , "glProgramUniform3fv" , "glProgramUniform3i" , "glProgramUniform3iv" , "glProgramUniform3ui" , "glProgramUniform3uiv" , "glProgramUniform4f" , "glProgramUniform4fv" , "glProgramUniform4i" , "glProgramUniform4iv" , "glProgramUniform4ui" , "glProgramUniform4uiv" , "glProgramUniformMatrix2fv" , "glProgramUniformMatrix2x3fv" , "glProgramUniformMatrix2x4fv" , "glProgramUniformMatrix3fv" , "glProgramUniformMatrix3x2fv" , "glProgramUniformMatrix3x4fv" , "glProgramUniformMatrix4fv" , "glProgramUniformMatrix4x2fv" , "glProgramUniformMatrix4x3fv" , "glProvokingVertex" , "glPushDebugGroup" , "glQueryCounter" , "glReadBuffer" , "glReadPixels" , "glReadnPixels" , "glReleaseShaderCompiler" , "glRenderbufferStorage" , "glRenderbufferStorageMultisample" , "glResumeTransformFeedback" , "glSampleCoverage" , "glSampleMaski" , "glSamplerParameter" , "glSamplerParameterIiv" , "glSamplerParameterIuiv" , "glSamplerParameterf" , "glSamplerParameterfv" , "glSamplerParameteri" , "glSamplerParameteriv" , "glScissor" , "glScissorArray" , "glScissorArrayv" , "glScissorIndexed" , "glScissorIndexedv" , "glShaderBinary" , "glShaderSource" , "glShaderStorageBlockBinding" , "glStencilFunc" , "glStencilFuncSeparate" , "glStencilMask" , "glStencilMaskSeparate" , "glStencilOp" , "glStencilOpSeparate" , "glTexBuffer" , "glTexBufferRange" , "glTexImage1D" , "glTexImage2D" , "glTexImage2DMultisample" , "glTexImage3D" , "glTexImage3DMultisample" , "glTexParameter" , "glTexParameterIiv" , "glTexParameterIuiv" , "glTexParameterf" , "glTexParameterfv" , "glTexParameteri" , "glTexParameteriv" , "glTexStorage1D" , "glTexStorage2D" , "glTexStorage2DMultisample" , "glTexStorage3D" , "glTexStorage3DMultisample" , "glTexSubImage1D" , "glTexSubImage2D" , "glTexSubImage3D" , "glTextureBarrier" , "glTextureBuffer" , "glTextureBufferRange" , "glTextureParameterIiv" , "glTextureParameterIuiv" , "glTextureParameterf" , "glTextureParameterfv" , "glTextureParameteri" , "glTextureParameteriv" , "glTextureStorage1D" , "glTextureStorage2D" , "glTextureStorage2DMultisample" , "glTextureStorage3D" , "glTextureStorage3DMultisample" , "glTextureSubImage1D" , "glTextureSubImage2D" , "glTextureSubImage3D" , "glTextureView" , "glTransformFeedbackBufferBase" , "glTransformFeedbackBufferRange" , "glTransformFeedbackVaryings" , "glUniform" , "glUniform1f" , "glUniform1fv" , "glUniform1i" , "glUniform1iv" , "glUniform1ui" , "glUniform1uiv" , "glUniform2f" , "glUniform2fv" , "glUniform2i" , "glUniform2iv" , "glUniform2ui" , "glUniform2uiv" , "glUniform3f" , "glUniform3fv" , "glUniform3i" , "glUniform3iv" , "glUniform3ui" , "glUniform3uiv" , "glUniform4f" , "glUniform4fv" , "glUniform4i" , "glUniform4iv" , "glUniform4ui" , "glUniform4uiv" , "glUniformBlockBinding" , "glUniformMatrix2fv" , "glUniformMatrix2x3fv" , "glUniformMatrix2x4fv" , "glUniformMatrix3fv" , "glUniformMatrix3x2fv" , "glUniformMatrix3x4fv" , "glUniformMatrix4fv" , "glUniformMatrix4x2fv" , "glUniformMatrix4x3fv" , "glUniformSubroutines" , "glUniformSubroutinesuiv" , "glUnmapBuffer" , "glUnmapNamedBuffer" , "glUseProgram" , "glUseProgramStages" , "glValidateProgram" , "glValidateProgramPipeline" , "glVertexArrayAttribBinding" , "glVertexArrayAttribFormat" , "glVertexArrayAttribIFormat" , "glVertexArrayAttribLFormat" , "glVertexArrayBindingDivisor" , "glVertexArrayElementBuffer" , "glVertexArrayVertexBuffer" , "glVertexArrayVertexBuffers" , "glVertexAttrib" , "glVertexAttrib1d" , "glVertexAttrib1dv" , "glVertexAttrib1f" , "glVertexAttrib1fv" , "glVertexAttrib1s" , "glVertexAttrib1sv" , "glVertexAttrib2d" , "glVertexAttrib2dv" , "glVertexAttrib2f" , "glVertexAttrib2fv" , "glVertexAttrib2s" , "glVertexAttrib2sv" , "glVertexAttrib3d" , "glVertexAttrib3dv" , "glVertexAttrib3f" , "glVertexAttrib3fv" , "glVertexAttrib3s" , "glVertexAttrib3sv" , "glVertexAttrib4Nbv" , "glVertexAttrib4Niv" , "glVertexAttrib4Nsv" , "glVertexAttrib4Nub" , "glVertexAttrib4Nubv" , "glVertexAttrib4Nuiv" , "glVertexAttrib4Nusv" , "glVertexAttrib4bv" , "glVertexAttrib4d" , "glVertexAttrib4dv" , "glVertexAttrib4f" , "glVertexAttrib4fv" , "glVertexAttrib4iv" , "glVertexAttrib4s" , "glVertexAttrib4sv" , "glVertexAttrib4ubv" , "glVertexAttrib4uiv" , "glVertexAttrib4usv" , "glVertexAttribBinding" , "glVertexAttribDivisor" , "glVertexAttribFormat" , "glVertexAttribI1i" , "glVertexAttribI1iv" , "glVertexAttribI1ui" , "glVertexAttribI1uiv" , "glVertexAttribI2i" , "glVertexAttribI2iv" , "glVertexAttribI2ui" , "glVertexAttribI2uiv" , "glVertexAttribI3i" , "glVertexAttribI3iv" , "glVertexAttribI3ui" , "glVertexAttribI3uiv" , "glVertexAttribI4bv" , "glVertexAttribI4i" , "glVertexAttribI4iv" , "glVertexAttribI4sv" , "glVertexAttribI4ubv" , "glVertexAttribI4ui" , "glVertexAttribI4uiv" , "glVertexAttribI4usv" , "glVertexAttribIFormat" , "glVertexAttribIPointer" , "glVertexAttribL1d" , "glVertexAttribL1dv" , "glVertexAttribL2d" , "glVertexAttribL2dv" , "glVertexAttribL3d" , "glVertexAttribL3dv" , "glVertexAttribL4d" , "glVertexAttribL4dv" , "glVertexAttribLFormat" , "glVertexAttribLPointer" , "glVertexAttribP1ui" , "glVertexAttribP2ui" , "glVertexAttribP3ui" , "glVertexAttribP4ui" , "glVertexAttribPointer" , "glVertexBindingDivisor" , "glViewport" , "glViewportArray" , "glViewportArrayv" , "glViewportIndexed" , "glViewportIndexedf" , "glViewportIndexedfv" , "glWaitSync" , "gl_ClipDistance" , "gl_CullDistance" , "gl_FragCoord" , "gl_FragDepth" , "gl_FrontFacing" , "gl_GlobalInvocationID" , "gl_HelperInvocation" , "gl_InstanceID" , "gl_InvocationID" , "gl_Layer" , "gl_LocalInvocationID" , "gl_LocalInvocationIndex" , "gl_NumSamples" , "gl_NumWorkGroups" , "gl_PatchVerticesIn" , "gl_PointCoord" , "gl_PointSize" , "gl_Position" , "gl_PrimitiveID" , "gl_PrimitiveIDIn" , "gl_SampleID" , "gl_SampleMask" , "gl_SampleMaskIn" , "gl_SamplePosition" , "gl_TessCoord" , "gl_TessLevelInner" , "gl_TessLevelOuter" , "gl_VertexID" , "gl_ViewportIndex" , "gl_WorkGroupID" , "gl_WorkGroupSize" , "greaterThan" , "greaterThanEqual" , "groupMemoryBarrier" , "imageAtomicAdd" , "imageAtomicAnd" , "imageAtomicCompSwap" , "imageAtomicExchange" , "imageAtomicMax" , "imageAtomicMin" , "imageAtomicOr" , "imageAtomicXor" , "imageLoad" , "imageSamples" , "imageSize" , "imageStore" , "imulExtended" , "intBitsToFloat" , "interpolateAtCentroid" , "interpolateAtOffset" , "interpolateAtSample" , "inverse" , "inversesqrt" , "isinf" , "isnan" , "ldexp" , "length" , "lessThan" , "lessThanEqual" , "log" , "log2" , "matrixCompMult" , "max" , "memoryBarrier" , "memoryBarrierAtomicCounter" , "memoryBarrierBuffer" , "memoryBarrierImage" , "memoryBarrierShared" , "min" , "mix" , "mod" , "modf" , "noise" , "noise1" , "noise2" , "noise3" , "noise4" , "normalize" , "not" , "notEqual" , "outerProduct" , "packDouble2x32" , "packHalf2x16" , "packSnorm2x16" , "packSnorm4x8" , "packUnorm" , "packUnorm2x16" , "packUnorm4x8" , "pow" , "radians" , "reflect" , "refract" , "removedTypes" , "round" , "roundEven" , "sign" , "sin" , "sinh" , "smoothstep" , "sqrt" , "step" , "tan" , "tanh" , "texelFetch" , "texelFetchOffset" , "texture" , "textureGather" , "textureGatherOffset" , "textureGatherOffsets" , "textureGrad" , "textureGradOffset" , "textureLod" , "textureLodOffset" , "textureOffset" , "textureProj" , "textureProjGrad" , "textureProjGradOffset" , "textureProjLod" , "textureProjLodOffset" , "textureProjOffset" , "textureQueryLevels" , "textureQueryLod" , "textureSamples" , "textureSize" , "transpose" , "trunc" , "uaddCarry" , "uintBitsToFloat" , "umulExtended" , "unpackDouble2x32" , "unpackHalf2x16" , "unpackSnorm2x16" , "unpackSnorm4x8" , "unpackUnorm" , "unpackUnorm2x16" , "unpackUnorm4x8" , "usubBorrow" ]) , rAttribute = BuiltInTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "gl_BackColor" , "gl_BackLightModelProduct" , "gl_BackLightProduct" , "gl_BackMaterial" , "gl_BackSecondaryColor" , "gl_ClipDistance" , "gl_ClipPlane" , "gl_ClipVertex" , "gl_Color" , "gl_DepthRange" , "gl_DepthRangeParameters" , "gl_EyePlaneQ" , "gl_EyePlaneR" , "gl_EyePlaneS" , "gl_EyePlaneT" , "gl_Fog" , "gl_FogColor" , "gl_FogFragCoord" , "gl_FogParameters" , "gl_FragColor" , "gl_FragCoord" , "gl_FragData" , "gl_FragDepth" , "gl_FragFacing" , "gl_FrontColor" , "gl_FrontLightModelProduct" , "gl_FrontLightProduct" , "gl_FrontMaterial" , "gl_FrontSecondaryColor" , "gl_InvocationID" , "gl_Layer" , "gl_LightModel" , "gl_LightModelParameters" , "gl_LightModelProducts" , "gl_LightProducts" , "gl_LightSource" , "gl_LightSourceParameters" , "gl_MaterialParameters" , "gl_MaxClipPlanes" , "gl_MaxCombinedTextureImageUnits" , "gl_MaxDrawBuffers" , "gl_MaxFragmentUniformComponents" , "gl_MaxLights" , "gl_MaxPatchVertices" , "gl_MaxTextureCoords" , "gl_MaxTextureImageUnits" , "gl_MaxTextureUnits" , "gl_MaxVaryingFloats" , "gl_MaxVertexAttributes" , "gl_MaxVertexTextureImageUnits" , "gl_MaxVertexUniformComponents" , "gl_ModelViewMatrix" , "gl_ModelViewMatrixInverse" , "gl_ModelViewMatrixInverseTranspose" , "gl_ModelViewMatrixTranspose" , "gl_ModelViewProjectionMatrix" , "gl_ModelViewProjectionMatrixInverse" , "gl_ModelViewProjectionMatrixInverseTranspose" , "gl_ModelViewProjectionMatrixTranspose" , "gl_MultiTexCoord0" , "gl_MultiTexCoord1" , "gl_MultiTexCoord2" , "gl_MultiTexCoord3" , "gl_MultiTexCoord4" , "gl_MultiTexCoord5" , "gl_MultiTexCoord6" , "gl_MultiTexCoord7" , "gl_NormScale" , "gl_Normal" , "gl_NormalMatrix" , "gl_ObjectPlaneQ" , "gl_ObjectPlaneR" , "gl_ObjectPlaneS" , "gl_ObjectPlaneT" , "gl_PatchVerticesIn" , "gl_Point" , "gl_PointParameters" , "gl_PointSize" , "gl_Position" , "gl_PrimitiveID" , "gl_PrimitiveIDIn" , "gl_ProjectionMatrix" , "gl_ProjectionMatrixInverse" , "gl_ProjectionMatrixInverseTranspose" , "gl_ProjectionMatrixTranspose" , "gl_SecondaryColor" , "gl_TessCoord" , "gl_TessLevelInner" , "gl_TessLevelOuter" , "gl_TexCoord" , "gl_TextureEnvColor" , "gl_TextureMatrix" , "gl_TextureMatrixInverse" , "gl_TextureMatrixInverseTranspose" , "gl_TextureMatrixTranspose" , "gl_Vertex" , "gl_ViewportIndex" , "gl_in" , "gl_out" ]) , rAttribute = VariableTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Float , rAttribute = FloatTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCOct , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCHex , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '/' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "GLSL" , "Commentar 1" ) ] } , Rule { rMatcher = Detect2Chars '/' '*' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "GLSL" , "Commentar 2" ) ] } , Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '#' , rAttribute = PreprocessorTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [ Push ( "GLSL" , "Preprocessor" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\b[_\\w][_\\w\\d]*(?=[\\s]*[(])" , reCompiled = Just (compileRegex True "\\b[_\\w][_\\w\\d]*(?=[\\s]*[(])") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[.]{1,1}" , reCompiled = Just (compileRegex True "[.]{1,1}") , reCaseSensitive = True } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "GLSL" , "Member" ) ] } , Rule { rMatcher = AnyChar ".+-/*%<>[]()^|&~=!:;,?;" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Preprocessor" , Context { cName = "Preprocessor" , cSyntax = "GLSL" , cRules = [] , cAttribute = PreprocessorTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Oliver Richers (o.richers@tu-bs.de)" , sVersion = "3" , sLicense = "LGPL" , sExtensions = [ "*.glsl" , "*.vert" , "*.frag" , "*.geom" , "*.tcs" , "*.tes" ] , sStartingContext = "Normal" }