{- This module was generated from data in the Kate syntax highlighting file glsl.xml, version 2, by Oliver Richers (o.richers@tu-bs.de) -} module Text.Highlighting.Kate.Syntax.Glsl (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import Text.ParserCombinators.Parsec hiding (State) import Control.Monad.State import Data.Char (isSpace) import qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "GLSL" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.glsl;*.vert;*.frag;*.geom;*.tcs;*.tes" -- | Highlight source code using this syntax definition. highlight :: String -> [SourceLine] highlight input = evalState (mapM parseSourceLine $ lines input) startingState parseSourceLine :: String -> State SyntaxState SourceLine parseSourceLine = mkParseSourceLine (parseExpression Nothing) -- | Parse an expression using appropriate local context. parseExpression :: Maybe (String,String) -> KateParser Token parseExpression mbcontext = do (lang,cont) <- maybe currentContext return mbcontext result <- parseRules (lang,cont) optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("GLSL","Normal")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStContinuation = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState st <- getState if length contexts >= 2 then case context of _ | synStContinuation st -> updateState $ \st -> st{ synStContinuation = False } ("GLSL","Normal") -> return () ("GLSL","Member") -> (popContext) >> pEndLine ("GLSL","Commentar 1") -> (popContext) >> pEndLine ("GLSL","Commentar 2") -> return () ("GLSL","Preprocessor") -> (popContext) >> pEndLine _ -> return () else return () withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" updateState $ \st -> st { synStPrevChar = last txt , synStPrevNonspace = synStPrevNonspace st || not (all isSpace txt) } return (attr, txt) list_keywords = Set.fromList $ words $ "break continue do for while if else true false discard return struct subroutine layout uniform buffer invariant" list_types = Set.fromList $ words $ "float int void bool mat2 mat3 mat4 vec2 vec3 vec4 ivec2 ivec3 ivec4 bvec2 bvec3 bvec4 sampler1D sampler2D sampler3D samplerCube sampler2DRect sampler1DArray sampler2DArray samplerCubeArray samplerBuffer sampler2DMS sampler2DMSArray sampler1DShadow sampler2DShadow samplerCubeShadow sampler2DRectShadow sampler1DArrayShadow sampler2DArrayShadow samplerCubeArrayShadow isampler1D isampler2D isampler3D isamplerCube isampler2DRect isampler1DArray isampler2DArray isamplerCubeArray isamplerBuffer isampler2DMS isampler2DMSArray isampler1DShadow isampler2DShadow isamplerCubeShadow isampler2DRectShadow isampler1DArrayShadow isampler2DArrayShadow isamplerCubeArrayShadow usampler1D usampler2D usampler3D usamplerCube usampler2DRect usampler1DArray usampler2DArray usamplerCubeArray usamplerBuffer usampler2DMS usampler2DMSArray usampler1DShadow usampler2DShadow usamplerCubeShadow usampler2DRectShadow usampler1DArrayShadow usampler2DArrayShadow usamplerCubeArrayShadow atomic_uint" list_typequal = Set.fromList $ words $ "attribute const varying in out inout flat noperspective smooth location component binding index offset row_major packed shared std140 std430 xfb_buffer xfb_offset xfb_stride origin_upper_left pixel_center_integer early_fragment_tests points lines lines_adjacency triangles triangles_adjacency line_strip triangle_strip max_vertices invocations stream isolines triangles quads point_mode equal_spacing fractional_even_spacing fractional_odd_spacing cw ccw vertices coherent volatile restrict readonly writeonly" list_attention = Set.fromList $ words $ "FIXME TODO BUG" list_stdlib = Set.fromList $ words $ "abs acos acosh glActiveShaderProgram glActiveTexture all any asin asinh atan atanh atomicAdd atomicAnd atomicCompSwap atomicCounter atomicCounterDecrement atomicCounterIncrement atomicExchange atomicMax atomicMin atomicOr atomicXor glAttachShader barrier glBeginConditionalRender glBeginQuery glBeginQueryIndexed glBeginTransformFeedback glBindAttribLocation glBindBuffer glBindBufferBase glBindBufferRange glBindBuffersBase glBindBuffersRange glBindFragDataLocation glBindFragDataLocationIndexed glBindFramebuffer glBindImageTexture glBindImageTextures glBindProgramPipeline glBindRenderbuffer glBindSampler glBindSamplers glBindTexture glBindTextures glBindTextureUnit glBindTransformFeedback glBindVertexArray glBindVertexBuffer glBindVertexBuffers bitCount bitfieldExtract bitfieldInsert bitfieldReverse glBlendColor glBlendEquation glBlendEquationi glBlendEquationSeparate glBlendEquationSeparatei glBlendFunc glBlendFunci glBlendFuncSeparate glBlendFuncSeparatei glBlitFramebuffer glBlitNamedFramebuffer glBufferData glBufferStorage glBufferSubData ceil glCheckFramebufferStatus glCheckNamedFramebufferStatus clamp glClampColor glClear glClearBuffer glClearBufferData glClearBufferfi glClearBufferfv glClearBufferiv glClearBufferSubData 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 cos cosh glCreateBuffers glCreateFramebuffers glCreateProgram glCreateProgramPipelines glCreateQueries glCreateRenderbuffers glCreateSamplers glCreateShader glCreateShaderProgram glCreateShaderProgramv glCreateTextures glCreateTransformFeedbacks glCreateVertexArrays cross glCullFace glDebugMessageCallback glDebugMessageControl glDebugMessageInsert degrees glDeleteBuffers glDeleteFramebuffers glDeleteProgram glDeleteProgramPipelines glDeleteQueries glDeleteRenderbuffers glDeleteSamplers glDeleteShader glDeleteSync glDeleteTextures glDeleteTransformFeedbacks glDeleteVertexArrays glDepthFunc glDepthMask glDepthRange glDepthRangeArray glDepthRangeArrayv glDepthRangef glDepthRangeIndexed glDetachShader determinant dFdx dFdxCoarse dFdxFine dFdy dFdyCoarse dFdyFine glDisable glDisablei glDisableVertexArrayAttrib glDisableVertexAttribArray glDispatchCompute glDispatchComputeIndirect distance dot glDrawArrays glDrawArraysIndirect glDrawArraysInstanced glDrawArraysInstancedBaseInstance glDrawBuffer glDrawBuffers glDrawElements glDrawElementsBaseVertex glDrawElementsIndirect glDrawElementsInstanced glDrawElementsInstancedBaseInstance glDrawElementsInstancedBaseVertex glDrawElementsInstancedBaseVertexBaseInstance glDrawRangeElements glDrawRangeElementsBaseVertex glDrawTransformFeedback glDrawTransformFeedbackInstanced glDrawTransformFeedbackStream glDrawTransformFeedbackStreamInstanced EmitStreamVertex EmitVertex glEnable glEnablei glEnableVertexArrayAttrib glEnableVertexAttribArray glEndConditionalRender EndPrimitive glEndQuery glEndQueryIndexed EndStreamPrimitive glEndTransformFeedback equal exp exp2 faceforward glFenceSync findLSB findMSB glFinish floatBitsToInt floatBitsToUint floor glFlush glFlushMappedBufferRange glFlushMappedNamedBufferRange fma fract glFramebufferParameteri glFramebufferRenderbuffer glFramebufferTexture glFramebufferTexture1D glFramebufferTexture2D glFramebufferTexture3D glFramebufferTextureLayer frexp glFrontFace fwidth fwidthCoarse fwidthFine glGenBuffers glGenerateMipmap glGenerateTextureMipmap glGenFramebuffers glGenProgramPipelines glGenQueries glGenRenderbuffers glGenSamplers glGenTextures glGenTransformFeedbacks glGenVertexArrays glGet glGetActiveAtomicCounterBufferiv glGetActiveAttrib glGetActiveSubroutineName glGetActiveSubroutineUniform glGetActiveSubroutineUniformiv glGetActiveSubroutineUniformName glGetActiveUniform glGetActiveUniformBlock glGetActiveUniformBlockiv glGetActiveUniformBlockName 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 glGetnCompressedTexImage glGetnTexImage glGetnUniformdv glGetnUniformfv glGetnUniformiv glGetnUniformuiv glGetObjectLabel glGetObjectPtrLabel glGetPointerv glGetProgram glGetProgramBinary glGetProgramInfoLog glGetProgramInterface glGetProgramInterfaceiv glGetProgramiv glGetProgramPipeline glGetProgramPipelineInfoLog glGetProgramPipelineiv glGetProgramResource glGetProgramResourceIndex glGetProgramResourceiv glGetProgramResourceLocation glGetProgramResourceLocationIndex glGetProgramResourceName glGetProgramStage glGetProgramStageiv glGetQueryIndexed glGetQueryIndexediv glGetQueryiv glGetQueryObject glGetQueryObjecti64v glGetQueryObjectiv glGetQueryObjectui64v glGetQueryObjectuiv glGetRenderbufferParameter glGetRenderbufferParameteriv glGetSamplerParameter glGetSamplerParameterfv glGetSamplerParameterIiv glGetSamplerParameterIuiv glGetSamplerParameteriv glGetShader glGetShaderInfoLog glGetShaderiv glGetShaderPrecisionFormat glGetShaderSource glGetString glGetStringi glGetSubroutineIndex glGetSubroutineUniformLocation glGetSync glGetSynciv glGetTexImage glGetTexLevelParameter glGetTexLevelParameterfv glGetTexLevelParameteriv glGetTexParameter glGetTexParameterfv glGetTexParameterIiv glGetTexParameterIuiv glGetTexParameteriv glGetTextureImage glGetTextureLevelParameterfv glGetTextureLevelParameteriv glGetTextureParameterfv glGetTextureParameterIiv glGetTextureParameterIuiv glGetTextureParameteriv glGetTextureSubImage glGetTransformFeedback glGetTransformFeedbacki64_v glGetTransformFeedbacki_v glGetTransformFeedbackiv glGetTransformFeedbackVarying glGetUniform glGetUniformBlockIndex glGetUniformdv glGetUniformfv glGetUniformIndices glGetUniformiv glGetUniformLocation glGetUniformSubroutine glGetUniformSubroutineuiv glGetUniformuiv glGetVertexArrayIndexed glGetVertexArrayIndexed64iv glGetVertexArrayIndexediv glGetVertexArrayiv glGetVertexAttrib glGetVertexAttribdv glGetVertexAttribfv glGetVertexAttribIiv glGetVertexAttribIuiv glGetVertexAttribiv glGetVertexAttribLdv glGetVertexAttribPointerv 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 glHint imageAtomicAdd imageAtomicAnd imageAtomicCompSwap imageAtomicExchange imageAtomicMax imageAtomicMin imageAtomicOr imageAtomicXor imageLoad imageSamples imageSize imageStore imulExtended intBitsToFloat interpolateAtCentroid interpolateAtOffset interpolateAtSample glInvalidateBufferData glInvalidateBufferSubData glInvalidateFramebuffer glInvalidateNamedFramebufferData glInvalidateNamedFramebufferSubData glInvalidateSubFramebuffer glInvalidateTexImage glInvalidateTexSubImage inverse inversesqrt glIsBuffer glIsEnabled glIsEnabledi glIsFramebuffer isinf isnan glIsProgram glIsProgramPipeline glIsQuery glIsRenderbuffer glIsSampler glIsShader glIsSync glIsTexture glIsTransformFeedback glIsVertexArray ldexp length lessThan lessThanEqual glLineWidth glLinkProgram log log2 glLogicOp glMapBuffer glMapBufferRange glMapNamedBuffer glMapNamedBufferRange matrixCompMult max memoryBarrier glMemoryBarrier memoryBarrierAtomicCounter memoryBarrierBuffer glMemoryBarrierByRegion memoryBarrierImage memoryBarrierShared min glMinSampleShading mix mod modf glMultiDrawArrays glMultiDrawArraysIndirect glMultiDrawElements glMultiDrawElementsBaseVertex glMultiDrawElementsIndirect glNamedBufferData glNamedBufferStorage glNamedBufferSubData glNamedFramebufferDrawBuffer glNamedFramebufferDrawBuffers glNamedFramebufferParameteri glNamedFramebufferReadBuffer glNamedFramebufferRenderbuffer glNamedFramebufferTexture glNamedFramebufferTextureLayer glNamedRenderbufferStorage glNamedRenderbufferStorageMultisample noise noise1 noise2 noise3 noise4 normalize not notEqual glObjectLabel glObjectPtrLabel outerProduct packDouble2x32 packHalf2x16 packSnorm2x16 packSnorm4x8 packUnorm packUnorm2x16 packUnorm4x8 glPatchParameter glPatchParameterfv glPatchParameteri glPauseTransformFeedback glPixelStore glPixelStoref glPixelStorei glPointParameter glPointParameterf glPointParameterfv glPointParameteri glPointParameteriv glPointSize glPolygonMode glPolygonOffset glPopDebugGroup pow 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 radians glReadBuffer glReadnPixels glReadPixels reflect refract glReleaseShaderCompiler removedTypes glRenderbufferStorage glRenderbufferStorageMultisample glResumeTransformFeedback round roundEven glSampleCoverage glSampleMaski glSamplerParameter glSamplerParameterf glSamplerParameterfv glSamplerParameteri glSamplerParameterIiv glSamplerParameterIuiv glSamplerParameteriv glScissor glScissorArray glScissorArrayv glScissorIndexed glScissorIndexedv glShaderBinary glShaderSource glShaderStorageBlockBinding sign sin sinh smoothstep sqrt glStencilFunc glStencilFuncSeparate glStencilMask glStencilMaskSeparate glStencilOp glStencilOpSeparate step tan tanh glTexBuffer glTexBufferRange texelFetch texelFetchOffset glTexImage1D glTexImage2D glTexImage2DMultisample glTexImage3D glTexImage3DMultisample glTexParameter glTexParameterf glTexParameterfv glTexParameteri glTexParameterIiv glTexParameterIuiv glTexParameteriv glTexStorage1D glTexStorage2D glTexStorage2DMultisample glTexStorage3D glTexStorage3DMultisample glTexSubImage1D glTexSubImage2D glTexSubImage3D texture glTextureBarrier glTextureBuffer glTextureBufferRange textureGather textureGatherOffset textureGatherOffsets textureGrad textureGradOffset textureLod textureLodOffset textureOffset glTextureParameterf glTextureParameterfv glTextureParameteri glTextureParameterIiv glTextureParameterIuiv glTextureParameteriv textureProj textureProjGrad textureProjGradOffset textureProjLod textureProjLodOffset textureProjOffset textureQueryLevels textureQueryLod textureSamples textureSize glTextureStorage1D glTextureStorage2D glTextureStorage2DMultisample glTextureStorage3D glTextureStorage3DMultisample glTextureSubImage1D glTextureSubImage2D glTextureSubImage3D glTextureView glTransformFeedbackBufferBase glTransformFeedbackBufferRange glTransformFeedbackVaryings transpose trunc uaddCarry uintBitsToFloat umulExtended 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 unpackDouble2x32 unpackHalf2x16 unpackSnorm2x16 unpackSnorm4x8 unpackUnorm unpackUnorm2x16 unpackUnorm4x8 glUseProgram glUseProgramStages usubBorrow 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 glVertexAttrib4bv glVertexAttrib4d glVertexAttrib4dv glVertexAttrib4f glVertexAttrib4fv glVertexAttrib4iv glVertexAttrib4Nbv glVertexAttrib4Niv glVertexAttrib4Nsv glVertexAttrib4Nub glVertexAttrib4Nubv glVertexAttrib4Nuiv glVertexAttrib4Nusv 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" list_stdvar = Set.fromList $ words $ "gl_Position gl_PointSize gl_ClipVertex gl_FragCoord gl_FragFacing gl_FragColor gl_FragData gl_FragDepth gl_Color gl_SecondaryColor gl_Normal gl_Vertex gl_MultiTexCoord0 gl_MultiTexCoord1 gl_MultiTexCoord2 gl_MultiTexCoord2 gl_MultiTexCoord3 gl_MultiTexCoord4 gl_MultiTexCoord5 gl_MultiTexCoord6 gl_MultiTexCoord7 gl_FogColor gl_ClipDistance gl_PrimitiveIDIn gl_InvocationID gl_PrimitiveID gl_Layer gl_ViewportIndex gl_TessCoord gl_PatchVerticesIn gl_TessLevelOuter gl_TessLevelInner gl_MaxPatchVertices gl_in gl_out gl_MaxLights gl_MaxClipPlanes gl_MaxTextureUnits gl_MaxTextureCoords gl_MaxVertexAttributes gl_MaxVertexUniformComponents gl_MaxVaryingFloats gl_MaxVertexTextureImageUnits gl_MaxCombinedTextureImageUnits gl_MaxTextureImageUnits gl_MaxFragmentUniformComponents gl_MaxDrawBuffers gl_ModelViewMatrix gl_ProjectionMatrix gl_ModelViewProjectionMatrix gl_TextureMatrix gl_NormalMatrix gl_ModelViewMatrixInverse gl_ProjectionMatrixInverse gl_ModelViewProjectionMatrixInverse gl_TextureMatrixInverse gl_ModelViewMatrixTranspose gl_ProjectionMatrixTranspose gl_ModelViewProjectionMatrixTranspose gl_TextureMatrixTranspose gl_ModelViewMatrixInverseTranspose gl_ProjectionMatrixInverseTranspose gl_ModelViewProjectionMatrixInverseTranspose gl_TextureMatrixInverseTranspose gl_NormScale gl_DepthRangeParameters gl_DepthRange gl_ClipPlane gl_PointParameters gl_Point gl_MaterialParameters gl_FrontMaterial gl_BackMaterial gl_LightSourceParameters gl_LightSource gl_LightModelParameters gl_LightModel gl_LightModelProducts gl_FrontLightModelProduct gl_BackLightModelProduct gl_LightProducts gl_FrontLightProduct gl_BackLightProduct gl_TextureEnvColor gl_EyePlaneS gl_EyePlaneT gl_EyePlaneR gl_EyePlaneQ gl_ObjectPlaneS gl_ObjectPlaneT gl_ObjectPlaneR gl_ObjectPlaneQ gl_FogParameters gl_Fog gl_FrontColor gl_BackColor gl_FrontSecondaryColor gl_BackSecondaryColor gl_TexCoord gl_FogFragCoord gl_Color gl_SecondaryColor" regex_'5cb'5b'5f'5cw'5d'5b'5f'5cw'5cd'5d'2a'28'3f'3d'5b'5cs'5d'2a'5b'28'5d'29 = compileRegex True "\\b[_\\w][_\\w\\d]*(?=[\\s]*[(])" regex_'5b'2e'5d'7b1'2c1'7d = compileRegex True "[.]{1,1}" regex_'5cb'5b'5f'5cw'5d'5b'5f'5cw'5cd'5d'2a'28'3f'3d'5b'5cs'5d'2a'29 = compileRegex True "\\b[_\\w][_\\w\\d]*(?=[\\s]*)" parseRules ("GLSL","Normal") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_types >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_typequal >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_stdlib >>= withAttribute BuiltInTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_stdvar >>= withAttribute VariableTok)) <|> ((pFloat >>= withAttribute FloatTok)) <|> ((pHlCOct >>= withAttribute BaseNTok)) <|> ((pHlCHex >>= withAttribute BaseNTok)) <|> ((pInt >>= withAttribute DecValTok)) <|> ((pDetect2Chars False '/' '/' >>= withAttribute CommentTok) >>~ pushContext ("GLSL","Commentar 1")) <|> ((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("GLSL","Commentar 2")) <|> ((pDetectChar False '{' >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok)) <|> ((pFirstNonSpace >> pDetectChar False '#' >>= withAttribute PreprocessorTok) >>~ pushContext ("GLSL","Preprocessor")) <|> ((pRegExpr regex_'5cb'5b'5f'5cw'5d'5b'5f'5cw'5cd'5d'2a'28'3f'3d'5b'5cs'5d'2a'5b'28'5d'29 >>= withAttribute FunctionTok)) <|> ((pRegExpr regex_'5b'2e'5d'7b1'2c1'7d >>= withAttribute NormalTok) >>~ pushContext ("GLSL","Member")) <|> ((pAnyChar ".+-/*%<>[]()^|&~=!:;,?;" >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("GLSL","Normal")) >> pDefault >>= withAttribute NormalTok)) parseRules ("GLSL","Member") = (((pRegExpr regex_'5cb'5b'5f'5cw'5d'5b'5f'5cw'5cd'5d'2a'28'3f'3d'5b'5cs'5d'2a'29 >>= withAttribute FunctionTok) >>~ (popContext)) <|> ((popContext) >> currentContext >>= parseRules)) parseRules ("GLSL","Commentar 1") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_attention >>= withAttribute AlertTok)) <|> (currentContext >>= \x -> guard (x == ("GLSL","Commentar 1")) >> pDefault >>= withAttribute CommentTok)) parseRules ("GLSL","Commentar 2") = (((pDetect2Chars False '*' '/' >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_attention >>= withAttribute AlertTok)) <|> (currentContext >>= \x -> guard (x == ("GLSL","Commentar 2")) >> pDefault >>= withAttribute CommentTok)) parseRules ("GLSL","Preprocessor") = (currentContext >>= \x -> guard (x == ("GLSL","Preprocessor")) >> pDefault >>= withAttribute PreprocessorTok) parseRules x = parseRules ("GLSL","Normal") <|> fail ("Unknown context" ++ show x)