{- This module was generated from data in the Kate syntax highlighting file glsl.xml, version 1.03, 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" -- | 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" 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 sampler1DShadow sampler2DShadow" list_typequal = Set.fromList $ words $ "attribute const uniform varying in out inout" list_attention = Set.fromList $ words $ "FIXME TODO BUG" list_stdlib = Set.fromList $ words $ "radians degrees sin cos tan asin acos atan pow exp log exp2 log2 sqrt inversesqrt abs sign floor ceil fract mod min max clamp mix step smoothstep length distance dot cross normalize ftransform faceforward reflect refract matrixCompMult lessThan lessThenEqual greaterThan greaterThanEqual equal notEqual any all not texture1D texture1DProj texture1DLod texture1DProjLod texture2D texture2DProj texture2DLod texture2DProjLod texture3D texture3DProj texture3DLod texture3DProjLod textureCube textureCubeLod shadow1D shadow2D shadow1DProj shadow2DProj shadow1DLod shadow2DLod shadow1DProjLod shadow2DProjLod dFdx dFdy fwidth noise1 noise2 noise3 noise4" 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_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 FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_stdvar >>= withAttribute FunctionTok)) <|> ((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 OtherTok) >>~ 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 OtherTok) parseRules x = parseRules ("GLSL","Normal") <|> fail ("Unknown context" ++ show x)