{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Jsp (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "JSP" , sFilename = "jsp.xml" , sShortname = "Jsp" , sContexts = fromList [ ( "Html Attribute" , Context { cName = "Html Attribute" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\/?>" , reCompiled = Just (compileRegex False "\\/?>") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*=\\s*" , reCompiled = Just (compileRegex False "\\s*=\\s*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Html Value" ) ] } , Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Html Comment" , Context { cName = "Html Comment" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\/*-->" , reCompiled = Just (compileRegex False "\\/*-->") , reCaseSensitive = False } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Html Double Quoted Value" , Context { cName = "Html Double Quoted Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<\\s*\\/?\\s*\\$?\\w*:\\$?\\w*" , reCompiled = Just (compileRegex False "<\\s*\\/?\\s*\\$?\\w*:\\$?\\w*") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Custom Tag" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(\"|"|")" , reCompiled = Just (compileRegex False "(\"|"|")") , reCaseSensitive = False } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Html Single Quoted Value" , Context { cName = "Html Single Quoted Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<\\s*\\/?\\s*\\$?\\w*:\\$?\\w*" , reCompiled = Just (compileRegex False "<\\s*\\/?\\s*\\$?\\w*:\\$?\\w*") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Custom Tag" ) ] } , Rule { rMatcher = RegExpr RE { reString = "('|')" , reCompiled = Just (compileRegex False "('|')") , reCaseSensitive = False } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Html Unquoted Value" , Context { cName = "Html Unquoted Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<\\s*\\/?\\s*\\$?\\w*:\\$?\\w*" , reCompiled = Just (compileRegex False "<\\s*\\/?\\s*\\$?\\w*:\\$?\\w*") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Custom Tag" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\/?>" , reCompiled = Just (compileRegex False "\\/?>") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop , Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\s+" , reCompiled = Just (compileRegex False "\\s+") , reCaseSensitive = False } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Html Value" , Context { cName = "Html Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<\\s*\\/?\\s*\\$?\\w*:\\$?\\w*" , reCompiled = Just (compileRegex False "<\\s*\\/?\\s*\\$?\\w*:\\$?\\w*") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Custom Tag" ) ] } , Rule { rMatcher = RegExpr RE { reString = "(\"|"|")" , reCompiled = Just (compileRegex False "(\"|"|")") , reCaseSensitive = False } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Html Double Quoted Value" ) ] } , Rule { rMatcher = RegExpr RE { reString = "('|')" , reCompiled = Just (compileRegex False "('|')") , reCaseSensitive = False } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Html Single Quoted Value" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*#?-?_?\\.?[a-zA-Z0-9]*" , reCompiled = Just (compileRegex False "\\s*#?-?_?\\.?[a-zA-Z0-9]*") , reCaseSensitive = False } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Html Unquoted Value" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\/?>" , reCompiled = Just (compileRegex False "\\/?>") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Java Multi-Line Comment" , Context { cName = "Java Multi-Line Comment" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = Detect2Chars '*' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Java Single-Line Comment" , Context { cName = "Java Single-Line Comment" , cSyntax = "JSP" , cRules = [] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Java String" , Context { cName = "Java String" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = Detect2Chars '\\' '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Comment" , Context { cName = "Jsp Comment" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = StringDetect "--%>" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Custom Tag" , Context { cName = "Jsp Custom Tag" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\/?>" , reCompiled = Just (compileRegex False "\\/?>") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*=\\s*" , reCompiled = Just (compileRegex False "\\s*=\\s*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Custom Tag Value" ) ] } , Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Custom Tag Value" , Context { cName = "Jsp Custom Tag Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } , Rule { rMatcher = DetectChar '"' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Double Quoted Custom Tag Value" ) ] } , Rule { rMatcher = DetectChar '\'' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Single Quoted Custom Tag Value" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\/?>" , reCompiled = Just (compileRegex False "\\/?>") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Double Quoted Custom Tag Value" , Context { cName = "Jsp Double Quoted Custom Tag Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = DetectChar '"' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Double Quoted Param Value" , Context { cName = "Jsp Double Quoted Param Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Expression" , Context { cName = "Jsp Expression" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = StringDetect "'${'" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "abstract" , "assert" , "break" , "case" , "catch" , "class" , "continue" , "default" , "do" , "else" , "extends" , "false" , "finally" , "for" , "goto" , "if" , "implements" , "import" , "instanceof" , "interface" , "native" , "new" , "null" , "package" , "private" , "protected" , "public" , "return" , "strictfp" , "super" , "switch" , "synchronized" , "this" , "throw" , "throws" , "transient" , "true" , "try" , "volatile" , "while" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "and" , "div" , "empty" , "eq" , "false" , "ge" , "gt" , "instanceof" , "le" , "lt" , "mod" , "ne" , "not" , "null" , "or" , "true" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "boolean" , "byte" , "char" , "const" , "double" , "final" , "float" , "int" , "long" , "short" , "static" , "void" ]) , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "ARG_IN" , "ARG_INOUT" , "ARG_OUT" , "AWTError" , "AWTEvent" , "AWTEventListener" , "AWTEventListenerProxy" , "AWTEventMulticaster" , "AWTException" , "AWTKeyStroke" , "AWTPermission" , "AbstractAction" , "AbstractBorder" , "AbstractButton" , "AbstractCellEditor" , "AbstractCollection" , "AbstractColorChooserPanel" , "AbstractDocument" , "AbstractFormatter" , "AbstractFormatterFactory" , "AbstractInterruptibleChannel" , "AbstractLayoutCache" , "AbstractList" , "AbstractListModel" , "AbstractMap" , "AbstractMethodError" , "AbstractPreferences" , "AbstractSelectableChannel" , "AbstractSelectionKey" , "AbstractSelector" , "AbstractSequentialList" , "AbstractSet" , "AbstractSpinnerModel" , "AbstractTableModel" , "AbstractUndoableEdit" , "AbstractWriter" , "AccessControlContext" , "AccessControlException" , "AccessController" , "AccessException" , "Accessible" , "AccessibleAction" , "AccessibleBundle" , "AccessibleComponent" , "AccessibleContext" , "AccessibleEditableText" , "AccessibleExtendedComponent" , "AccessibleExtendedTable" , "AccessibleHyperlink" , "AccessibleHypertext" , "AccessibleIcon" , "AccessibleKeyBinding" , "AccessibleObject" , "AccessibleRelation" , "AccessibleRelationSet" , "AccessibleResourceBundle" , "AccessibleRole" , "AccessibleSelection" , "AccessibleState" , "AccessibleStateSet" , "AccessibleTable" , "AccessibleTableModelChange" , "AccessibleText" , "AccessibleValue" , "AccountExpiredException" , "Acl" , "AclEntry" , "AclNotFoundException" , "Action" , "ActionEvent" , "ActionListener" , "ActionMap" , "ActionMapUIResource" , "Activatable" , "ActivateFailedException" , "ActivationDesc" , "ActivationException" , "ActivationGroup" , "ActivationGroupDesc" , "ActivationGroupID" , "ActivationGroup_Stub" , "ActivationID" , "ActivationInstantiator" , "ActivationMonitor" , "ActivationSystem" , "Activator" , "ActiveEvent" , "ActiveValue" , "AdapterActivator" , "AdapterActivatorOperations" , "AdapterAlreadyExists" , "AdapterAlreadyExistsHelper" , "AdapterInactive" , "AdapterInactiveHelper" , "AdapterNonExistent" , "AdapterNonExistentHelper" , "AddressHelper" , "Adjustable" , "AdjustmentEvent" , "AdjustmentListener" , "Adler32" , "AffineTransform" , "AffineTransformOp" , "AlgorithmParameterGenerator" , "AlgorithmParameterGeneratorSpi" , "AlgorithmParameterSpec" , "AlgorithmParameters" , "AlgorithmParametersSpi" , "AlignmentAction" , "AllPermission" , "AlphaComposite" , "AlreadyBound" , "AlreadyBoundException" , "AlreadyBoundHelper" , "AlreadyBoundHolder" , "AlreadyConnectedException" , "AncestorEvent" , "AncestorListener" , "Annotation" , "Any" , "AnyHolder" , "AnySeqHelper" , "AnySeqHolder" , "AppConfigurationEntry" , "Applet" , "AppletContext" , "AppletInitializer" , "AppletStub" , "ApplicationException" , "Arc2D" , "Area" , "AreaAveragingScaleFilter" , "ArithmeticException" , "Array" , "ArrayIndexOutOfBoundsException" , "ArrayList" , "ArrayStoreException" , "Arrays" , "AssertionError" , "AsyncBoxView" , "AsynchronousCloseException" , "Attr" , "Attribute" , "AttributeContext" , "AttributeException" , "AttributeInUseException" , "AttributeList" , "AttributeListImpl" , "AttributeModificationException" , "AttributeSet" , "AttributeSetUtilities" , "AttributeUndoableEdit" , "AttributedCharacterIterator" , "AttributedString" , "Attributes" , "AttributesImpl" , "AudioClip" , "AudioFileFormat" , "AudioFileReader" , "AudioFileWriter" , "AudioFormat" , "AudioInputStream" , "AudioPermission" , "AudioSystem" , "AuthPermission" , "AuthenticationException" , "AuthenticationNotSupportedException" , "Authenticator" , "Autoscroll" , "BAD_CONTEXT" , "BAD_INV_ORDER" , "BAD_OPERATION" , "BAD_PARAM" , "BAD_POLICY" , "BAD_POLICY_TYPE" , "BAD_POLICY_VALUE" , "BAD_TYPECODE" , "BCSIterator" , "BCSSServiceProvider" , "BYTE_ARRAY" , "BackingStoreException" , "BadKind" , "BadLocationException" , "BadPaddingException" , "BandCombineOp" , "BandedSampleModel" , "BasicArrowButton" , "BasicAttribute" , "BasicAttributes" , "BasicBorders" , "BasicButtonListener" , "BasicButtonUI" , "BasicCaret" , "BasicCheckBoxMenuItemUI" , "BasicCheckBoxUI" , "BasicColorChooserUI" , "BasicComboBoxEditor" , "BasicComboBoxRenderer" , "BasicComboBoxUI" , "BasicComboPopup" , "BasicDesktopIconUI" , "BasicDesktopPaneUI" , "BasicDirectoryModel" , "BasicEditorPaneUI" , "BasicFileChooserUI" , "BasicFormattedTextFieldUI" , "BasicGraphicsUtils" , "BasicHTML" , "BasicHighlighter" , "BasicIconFactory" , "BasicInternalFrameTitlePane" , "BasicInternalFrameUI" , "BasicLabelUI" , "BasicListUI" , "BasicLookAndFeel" , "BasicMenuBarUI" , "BasicMenuItemUI" , "BasicMenuUI" , "BasicOptionPaneUI" , "BasicPanelUI" , "BasicPasswordFieldUI" , "BasicPermission" , "BasicPopupMenuSeparatorUI" , "BasicPopupMenuUI" , "BasicProgressBarUI" , "BasicRadioButtonMenuItemUI" , "BasicRadioButtonUI" , "BasicRootPaneUI" , "BasicScrollBarUI" , "BasicScrollPaneUI" , "BasicSeparatorUI" , "BasicSliderUI" , "BasicSpinnerUI" , "BasicSplitPaneDivider" , "BasicSplitPaneUI" , "BasicStroke" , "BasicTabbedPaneUI" , "BasicTableHeaderUI" , "BasicTableUI" , "BasicTextAreaUI" , "BasicTextFieldUI" , "BasicTextPaneUI" , "BasicTextUI" , "BasicToggleButtonUI" , "BasicToolBarSeparatorUI" , "BasicToolBarUI" , "BasicToolTipUI" , "BasicTreeUI" , "BasicViewportUI" , "BatchUpdateException" , "BeanContext" , "BeanContextChild" , "BeanContextChildComponentProxy" , "BeanContextChildSupport" , "BeanContextContainerProxy" , "BeanContextEvent" , "BeanContextMembershipEvent" , "BeanContextMembershipListener" , "BeanContextProxy" , "BeanContextServiceAvailableEvent" , "BeanContextServiceProvider" , "BeanContextServiceProviderBeanInfo" , "BeanContextServiceRevokedEvent" , "BeanContextServiceRevokedListener" , "BeanContextServices" , "BeanContextServicesListener" , "BeanContextServicesSupport" , "BeanContextSupport" , "BeanDescriptor" , "BeanInfo" , "Beans" , "BeepAction" , "BevelBorder" , "BevelBorderUIResource" , "Bias" , "Bidi" , "BigDecimal" , "BigInteger" , "BinaryRefAddr" , "BindException" , "Binding" , "BindingHelper" , "BindingHolder" , "BindingIterator" , "BindingIteratorHelper" , "BindingIteratorHolder" , "BindingIteratorOperations" , "BindingIteratorPOA" , "BindingListHelper" , "BindingListHolder" , "BindingType" , "BindingTypeHelper" , "BindingTypeHolder" , "BitSet" , "Blob" , "BlockView" , "BoldAction" , "Book" , "Boolean" , "BooleanControl" , "BooleanHolder" , "BooleanSeqHelper" , "BooleanSeqHolder" , "Border" , "BorderFactory" , "BorderLayout" , "BorderUIResource" , "BoundedRangeModel" , "Bounds" , "Box" , "BoxLayout" , "BoxPainter" , "BoxView" , "BoxedValueHelper" , "BreakIterator" , "Buffer" , "BufferCapabilities" , "BufferOverflowException" , "BufferStrategy" , "BufferUnderflowException" , "BufferedImage" , "BufferedImageFilter" , "BufferedImageOp" , "BufferedInputStream" , "BufferedOutputStream" , "BufferedReader" , "BufferedWriter" , "Button" , "ButtonAreaLayout" , "ButtonBorder" , "ButtonGroup" , "ButtonModel" , "ButtonUI" , "Byte" , "ByteArrayInputStream" , "ByteArrayOutputStream" , "ByteBuffer" , "ByteChannel" , "ByteHolder" , "ByteLookupTable" , "ByteOrder" , "CDATASection" , "CHAR_ARRAY" , "CMMException" , "COMM_FAILURE" , "CRC32" , "CRL" , "CRLException" , "CRLSelector" , "CSS" , "CTX_RESTRICT_SCOPE" , "Calendar" , "CallableStatement" , "Callback" , "CallbackHandler" , "CancelablePrintJob" , "CancelledKeyException" , "CannotProceed" , "CannotProceedException" , "CannotProceedHelper" , "CannotProceedHolder" , "CannotRedoException" , "CannotUndoException" , "Canvas" , "CardLayout" , "Caret" , "CaretEvent" , "CaretListener" , "CaretPolicy" , "CellEditor" , "CellEditorListener" , "CellRendererPane" , "CertPath" , "CertPathBuilder" , "CertPathBuilderException" , "CertPathBuilderResult" , "CertPathBuilderSpi" , "CertPathParameters" , "CertPathRep" , "CertPathValidator" , "CertPathValidatorException" , "CertPathValidatorResult" , "CertPathValidatorSpi" , "CertSelector" , "CertStore" , "CertStoreException" , "CertStoreParameters" , "CertStoreSpi" , "Certificate" , "CertificateEncodingException" , "CertificateException" , "CertificateExpiredException" , "CertificateFactory" , "CertificateFactorySpi" , "CertificateNotYetValidException" , "CertificateParsingException" , "CertificateRep" , "ChangeEvent" , "ChangeListener" , "ChangedCharSetException" , "Channel" , "ChannelBinding" , "Channels" , "CharArrayReader" , "CharArrayWriter" , "CharBuffer" , "CharConversionException" , "CharHolder" , "CharSeqHelper" , "CharSeqHolder" , "CharSequence" , "Character" , "CharacterAttribute" , "CharacterCodingException" , "CharacterConstants" , "CharacterData" , "CharacterIterator" , "Charset" , "CharsetDecoder" , "CharsetEncoder" , "CharsetProvider" , "Checkbox" , "CheckboxGroup" , "CheckboxMenuItem" , "CheckedInputStream" , "CheckedOutputStream" , "Checksum" , "Choice" , "ChoiceCallback" , "ChoiceFormat" , "Chromaticity" , "Cipher" , "CipherInputStream" , "CipherOutputStream" , "CipherSpi" , "Class" , "ClassCastException" , "ClassCircularityError" , "ClassDesc" , "ClassFormatError" , "ClassLoader" , "ClassNotFoundException" , "ClientRequestInfo" , "ClientRequestInfoOperations" , "ClientRequestInterceptor" , "ClientRequestInterceptorOperations" , "Clip" , "Clipboard" , "ClipboardOwner" , "Clob" , "CloneNotSupportedException" , "Cloneable" , "ClosedByInterruptException" , "ClosedChannelException" , "ClosedSelectorException" , "CodeSets" , "CodeSource" , "Codec" , "CodecFactory" , "CodecFactoryHelper" , "CodecFactoryOperations" , "CodecOperations" , "CoderMalfunctionError" , "CoderResult" , "CodingErrorAction" , "CollationElementIterator" , "CollationKey" , "Collator" , "Collection" , "CollectionCertStoreParameters" , "Collections" , "Color" , "ColorAttribute" , "ColorChooserComponentFactory" , "ColorChooserUI" , "ColorConstants" , "ColorConvertOp" , "ColorModel" , "ColorSelectionModel" , "ColorSpace" , "ColorSupported" , "ColorType" , "ColorUIResource" , "ComboBoxEditor" , "ComboBoxModel" , "ComboBoxUI" , "ComboPopup" , "CommandEnvironment" , "Comment" , "CommunicationException" , "Comparable" , "Comparator" , "Compiler" , "CompletionStatus" , "CompletionStatusHelper" , "Component" , "ComponentAdapter" , "ComponentColorModel" , "ComponentEvent" , "ComponentIdHelper" , "ComponentInputMap" , "ComponentInputMapUIResource" , "ComponentListener" , "ComponentOrientation" , "ComponentSampleModel" , "ComponentUI" , "ComponentView" , "Composite" , "CompositeContext" , "CompositeName" , "CompositeView" , "CompoundBorder" , "CompoundBorderUIResource" , "CompoundControl" , "CompoundEdit" , "CompoundName" , "Compression" , "ConcurrentModificationException" , "Configuration" , "ConfigurationException" , "ConfirmationCallback" , "ConnectException" , "ConnectIOException" , "Connection" , "ConnectionEvent" , "ConnectionEventListener" , "ConnectionPendingException" , "ConnectionPoolDataSource" , "ConsoleHandler" , "Constraints" , "Constructor" , "Container" , "ContainerAdapter" , "ContainerEvent" , "ContainerListener" , "ContainerOrderFocusTraversalPolicy" , "Content" , "ContentHandler" , "ContentHandlerFactory" , "ContentModel" , "Context" , "ContextList" , "ContextNotEmptyException" , "ContextualRenderedImageFactory" , "Control" , "ControlFactory" , "ControllerEventListener" , "ConvolveOp" , "CookieHolder" , "Copies" , "CopiesSupported" , "CopyAction" , "CredentialExpiredException" , "CropImageFilter" , "CubicCurve2D" , "Currency" , "Current" , "CurrentHelper" , "CurrentHolder" , "CurrentOperations" , "Cursor" , "CustomMarshal" , "CustomValue" , "Customizer" , "CutAction" , "DATA_CONVERSION" , "DESKeySpec" , "DESedeKeySpec" , "DGC" , "DHGenParameterSpec" , "DHKey" , "DHParameterSpec" , "DHPrivateKey" , "DHPrivateKeySpec" , "DHPublicKey" , "DHPublicKeySpec" , "DOMException" , "DOMImplementation" , "DOMLocator" , "DOMResult" , "DOMSource" , "DSAKey" , "DSAKeyPairGenerator" , "DSAParameterSpec" , "DSAParams" , "DSAPrivateKey" , "DSAPrivateKeySpec" , "DSAPublicKey" , "DSAPublicKeySpec" , "DTD" , "DTDConstants" , "DTDHandler" , "DataBuffer" , "DataBufferByte" , "DataBufferDouble" , "DataBufferFloat" , "DataBufferInt" , "DataBufferShort" , "DataBufferUShort" , "DataFlavor" , "DataFormatException" , "DataInput" , "DataInputStream" , "DataLine" , "DataOutput" , "DataOutputStream" , "DataSource" , "DataTruncation" , "DatabaseMetaData" , "DatagramChannel" , "DatagramPacket" , "DatagramSocket" , "DatagramSocketImpl" , "DatagramSocketImplFactory" , "Date" , "DateEditor" , "DateFormat" , "DateFormatSymbols" , "DateFormatter" , "DateTimeAtCompleted" , "DateTimeAtCreation" , "DateTimeAtProcessing" , "DateTimeSyntax" , "DebugGraphics" , "DecimalFormat" , "DecimalFormatSymbols" , "DeclHandler" , "DefaultBoundedRangeModel" , "DefaultButtonModel" , "DefaultCaret" , "DefaultCellEditor" , "DefaultColorSelectionModel" , "DefaultComboBoxModel" , "DefaultDesktopManager" , "DefaultEditor" , "DefaultEditorKit" , "DefaultFocusManager" , "DefaultFocusTraversalPolicy" , "DefaultFormatter" , "DefaultFormatterFactory" , "DefaultHandler" , "DefaultHighlightPainter" , "DefaultHighlighter" , "DefaultKeyTypedAction" , "DefaultKeyboardFocusManager" , "DefaultListCellRenderer" , "DefaultListModel" , "DefaultListSelectionModel" , "DefaultMenuLayout" , "DefaultMetalTheme" , "DefaultMutableTreeNode" , "DefaultPersistenceDelegate" , "DefaultSelectionType" , "DefaultSingleSelectionModel" , "DefaultStyledDocument" , "DefaultTableCellRenderer" , "DefaultTableColumnModel" , "DefaultTableModel" , "DefaultTextUI" , "DefaultTreeCellEditor" , "DefaultTreeCellRenderer" , "DefaultTreeModel" , "DefaultTreeSelectionModel" , "DefinitionKind" , "DefinitionKindHelper" , "Deflater" , "DeflaterOutputStream" , "Delegate" , "DelegationPermission" , "DesignMode" , "DesktopIconUI" , "DesktopManager" , "DesktopPaneUI" , "Destination" , "DestinationType" , "DestroyFailedException" , "Destroyable" , "Dialog" , "DialogType" , "Dictionary" , "DigestException" , "DigestInputStream" , "DigestOutputStream" , "Dimension" , "Dimension2D" , "DimensionUIResource" , "DirContext" , "DirObjectFactory" , "DirStateFactory" , "DirectColorModel" , "DirectoryManager" , "DisplayMode" , "DnDConstants" , "Doc" , "DocAttribute" , "DocAttributeSet" , "DocFlavor" , "DocPrintJob" , "Document" , "DocumentBuilder" , "DocumentBuilderFactory" , "DocumentEvent" , "DocumentFilter" , "DocumentFragment" , "DocumentHandler" , "DocumentListener" , "DocumentName" , "DocumentParser" , "DocumentType" , "DomainCombiner" , "DomainManager" , "DomainManagerOperations" , "Double" , "DoubleBuffer" , "DoubleHolder" , "DoubleSeqHelper" , "DoubleSeqHolder" , "DragGestureEvent" , "DragGestureListener" , "DragGestureRecognizer" , "DragSource" , "DragSourceAdapter" , "DragSourceContext" , "DragSourceDragEvent" , "DragSourceDropEvent" , "DragSourceEvent" , "DragSourceListener" , "DragSourceMotionListener" , "Driver" , "DriverManager" , "DriverPropertyInfo" , "DropTarget" , "DropTargetAdapter" , "DropTargetAutoScroller" , "DropTargetContext" , "DropTargetDragEvent" , "DropTargetDropEvent" , "DropTargetEvent" , "DropTargetListener" , "DuplicateName" , "DuplicateNameHelper" , "DynAny" , "DynAnyFactory" , "DynAnyFactoryHelper" , "DynAnyFactoryOperations" , "DynAnyHelper" , "DynAnyOperations" , "DynAnySeqHelper" , "DynArray" , "DynArrayHelper" , "DynArrayOperations" , "DynEnum" , "DynEnumHelper" , "DynEnumOperations" , "DynFixed" , "DynFixedHelper" , "DynFixedOperations" , "DynSequence" , "DynSequenceHelper" , "DynSequenceOperations" , "DynStruct" , "DynStructHelper" , "DynStructOperations" , "DynUnion" , "DynUnionHelper" , "DynUnionOperations" , "DynValue" , "DynValueBox" , "DynValueBoxOperations" , "DynValueCommon" , "DynValueCommonOperations" , "DynValueHelper" , "DynValueOperations" , "DynamicImplementation" , "DynamicUtilTreeNode" , "ENCODING_CDR_ENCAPS" , "EOFException" , "EditorKit" , "Element" , "ElementChange" , "ElementEdit" , "ElementIterator" , "ElementSpec" , "Ellipse2D" , "EmptyBorder" , "EmptyBorderUIResource" , "EmptySelectionModel" , "EmptyStackException" , "EncodedKeySpec" , "Encoder" , "Encoding" , "EncryptedPrivateKeyInfo" , "Engineering" , "Entity" , "EntityReference" , "EntityResolver" , "Entry" , "EnumControl" , "EnumSyntax" , "Enumeration" , "Environment" , "Error" , "ErrorHandler" , "ErrorListener" , "ErrorManager" , "EtchedBorder" , "EtchedBorderUIResource" , "Event" , "EventContext" , "EventDirContext" , "EventHandler" , "EventListener" , "EventListenerList" , "EventListenerProxy" , "EventObject" , "EventQueue" , "EventSetDescriptor" , "EventType" , "Exception" , "ExceptionInInitializerError" , "ExceptionList" , "ExceptionListener" , "ExemptionMechanism" , "ExemptionMechanismException" , "ExemptionMechanismSpi" , "ExpandVetoException" , "ExportException" , "Expression" , "ExtendedRequest" , "ExtendedResponse" , "Externalizable" , "FREE_MEM" , "FactoryConfigurationError" , "FailedLoginException" , "FeatureDescriptor" , "Fidelity" , "Field" , "FieldBorder" , "FieldNameHelper" , "FieldPosition" , "FieldView" , "File" , "FileCacheImageInputStream" , "FileCacheImageOutputStream" , "FileChannel" , "FileChooserUI" , "FileDescriptor" , "FileDialog" , "FileFilter" , "FileHandler" , "FileIcon16" , "FileImageInputStream" , "FileImageOutputStream" , "FileInputStream" , "FileLock" , "FileLockInterruptionException" , "FileNameMap" , "FileNotFoundException" , "FileOutputStream" , "FilePermission" , "FileReader" , "FileSystemView" , "FileView" , "FileWriter" , "FilenameFilter" , "Filler" , "Filter" , "FilterBypass" , "FilterInputStream" , "FilterOutputStream" , "FilterReader" , "FilterWriter" , "FilteredImageSource" , "Finishings" , "FixedHeightLayoutCache" , "FixedHolder" , "FlatteningPathIterator" , "FlavorException" , "FlavorMap" , "FlavorTable" , "FlipContents" , "Float" , "FloatBuffer" , "FloatControl" , "FloatHolder" , "FloatSeqHelper" , "FloatSeqHolder" , "FlowLayout" , "FlowStrategy" , "FlowView" , "Flush3DBorder" , "FocusAdapter" , "FocusEvent" , "FocusListener" , "FocusManager" , "FocusTraversalPolicy" , "FolderIcon16" , "Font" , "FontAttribute" , "FontConstants" , "FontFamilyAction" , "FontFormatException" , "FontMetrics" , "FontRenderContext" , "FontSizeAction" , "FontUIResource" , "ForegroundAction" , "FormView" , "Format" , "FormatConversionProvider" , "FormatMismatch" , "FormatMismatchHelper" , "Formatter" , "ForwardRequest" , "ForwardRequestHelper" , "Frame" , "GSSContext" , "GSSCredential" , "GSSException" , "GSSManager" , "GSSName" , "GZIPInputStream" , "GZIPOutputStream" , "GapContent" , "GatheringByteChannel" , "GeneralPath" , "GeneralSecurityException" , "GetField" , "GlyphJustificationInfo" , "GlyphMetrics" , "GlyphPainter" , "GlyphVector" , "GlyphView" , "GradientPaint" , "GraphicAttribute" , "Graphics" , "Graphics2D" , "GraphicsConfigTemplate" , "GraphicsConfiguration" , "GraphicsDevice" , "GraphicsEnvironment" , "GrayFilter" , "GregorianCalendar" , "GridBagConstraints" , "GridBagLayout" , "GridLayout" , "Group" , "Guard" , "GuardedObject" , "HTML" , "HTMLDocument" , "HTMLEditorKit" , "HTMLFrameHyperlinkEvent" , "HTMLWriter" , "Handler" , "HandlerBase" , "HandshakeCompletedEvent" , "HandshakeCompletedListener" , "HasControls" , "HashAttributeSet" , "HashDocAttributeSet" , "HashMap" , "HashPrintJobAttributeSet" , "HashPrintRequestAttributeSet" , "HashPrintServiceAttributeSet" , "HashSet" , "Hashtable" , "HeadlessException" , "HierarchyBoundsAdapter" , "HierarchyBoundsListener" , "HierarchyEvent" , "HierarchyListener" , "Highlight" , "HighlightPainter" , "Highlighter" , "HostnameVerifier" , "HttpURLConnection" , "HttpsURLConnection" , "HyperlinkEvent" , "HyperlinkListener" , "ICC_ColorSpace" , "ICC_Profile" , "ICC_ProfileGray" , "ICC_ProfileRGB" , "IDLEntity" , "IDLType" , "IDLTypeHelper" , "IDLTypeOperations" , "ID_ASSIGNMENT_POLICY_ID" , "ID_UNIQUENESS_POLICY_ID" , "IIOByteBuffer" , "IIOException" , "IIOImage" , "IIOInvalidTreeException" , "IIOMetadata" , "IIOMetadataController" , "IIOMetadataFormat" , "IIOMetadataFormatImpl" , "IIOMetadataNode" , "IIOParam" , "IIOParamController" , "IIOReadProgressListener" , "IIOReadUpdateListener" , "IIOReadWarningListener" , "IIORegistry" , "IIOServiceProvider" , "IIOWriteProgressListener" , "IIOWriteWarningListener" , "IMPLICIT_ACTIVATION_POLICY_ID" , "IMP_LIMIT" , "INITIALIZE" , "INPUT_STREAM" , "INTERNAL" , "INTF_REPOS" , "INVALID_TRANSACTION" , "INV_FLAG" , "INV_IDENT" , "INV_OBJREF" , "INV_POLICY" , "IOException" , "IOR" , "IORHelper" , "IORHolder" , "IORInfo" , "IORInfoOperations" , "IORInterceptor" , "IORInterceptorOperations" , "IRObject" , "IRObjectOperations" , "ISO" , "Icon" , "IconUIResource" , "IconView" , "IdAssignmentPolicy" , "IdAssignmentPolicyOperations" , "IdAssignmentPolicyValue" , "IdUniquenessPolicy" , "IdUniquenessPolicyOperations" , "IdUniquenessPolicyValue" , "IdentifierHelper" , "Identity" , "IdentityHashMap" , "IdentityScope" , "IllegalAccessError" , "IllegalAccessException" , "IllegalArgumentException" , "IllegalBlockSizeException" , "IllegalBlockingModeException" , "IllegalCharsetNameException" , "IllegalComponentStateException" , "IllegalMonitorStateException" , "IllegalPathStateException" , "IllegalSelectorException" , "IllegalStateException" , "IllegalThreadStateException" , "Image" , "ImageCapabilities" , "ImageConsumer" , "ImageFilter" , "ImageGraphicAttribute" , "ImageIO" , "ImageIcon" , "ImageInputStream" , "ImageInputStreamImpl" , "ImageInputStreamSpi" , "ImageObserver" , "ImageOutputStream" , "ImageOutputStreamImpl" , "ImageOutputStreamSpi" , "ImageProducer" , "ImageReadParam" , "ImageReader" , "ImageReaderSpi" , "ImageReaderWriterSpi" , "ImageTranscoder" , "ImageTranscoderSpi" , "ImageTypeSpecifier" , "ImageView" , "ImageWriteParam" , "ImageWriter" , "ImageWriterSpi" , "ImagingOpException" , "ImplicitActivationPolicy" , "ImplicitActivationPolicyOperations" , "ImplicitActivationPolicyValue" , "IncompatibleClassChangeError" , "InconsistentTypeCode" , "InconsistentTypeCodeHelper" , "IndexColorModel" , "IndexOutOfBoundsException" , "IndexedPropertyDescriptor" , "IndirectionException" , "Inet4Address" , "Inet6Address" , "InetAddress" , "InetSocketAddress" , "Inflater" , "InflaterInputStream" , "Info" , "InheritableThreadLocal" , "InitialContext" , "InitialContextFactory" , "InitialContextFactoryBuilder" , "InitialDirContext" , "InitialLdapContext" , "InlineView" , "InputContext" , "InputEvent" , "InputMap" , "InputMapUIResource" , "InputMethod" , "InputMethodContext" , "InputMethodDescriptor" , "InputMethodEvent" , "InputMethodHighlight" , "InputMethodListener" , "InputMethodRequests" , "InputSource" , "InputStream" , "InputStreamReader" , "InputSubset" , "InputVerifier" , "InsertBreakAction" , "InsertContentAction" , "InsertHTMLTextAction" , "InsertTabAction" , "Insets" , "InsetsUIResource" , "InstantiationError" , "InstantiationException" , "Instrument" , "InsufficientResourcesException" , "IntBuffer" , "IntHolder" , "Integer" , "IntegerSyntax" , "Interceptor" , "InterceptorOperations" , "InternalError" , "InternalFrameAdapter" , "InternalFrameBorder" , "InternalFrameEvent" , "InternalFrameFocusTraversalPolicy" , "InternalFrameListener" , "InternalFrameUI" , "InternationalFormatter" , "InterruptedException" , "InterruptedIOException" , "InterruptedNamingException" , "InterruptibleChannel" , "IntrospectionException" , "Introspector" , "Invalid" , "InvalidAddress" , "InvalidAddressHelper" , "InvalidAddressHolder" , "InvalidAlgorithmParameterException" , "InvalidAttributeIdentifierException" , "InvalidAttributeValueException" , "InvalidAttributesException" , "InvalidClassException" , "InvalidDnDOperationException" , "InvalidKeyException" , "InvalidKeySpecException" , "InvalidMarkException" , "InvalidMidiDataException" , "InvalidName" , "InvalidNameException" , "InvalidNameHelper" , "InvalidNameHolder" , "InvalidObjectException" , "InvalidParameterException" , "InvalidParameterSpecException" , "InvalidPolicy" , "InvalidPolicyHelper" , "InvalidPreferencesFormatException" , "InvalidSearchControlsException" , "InvalidSearchFilterException" , "InvalidSeq" , "InvalidSlot" , "InvalidSlotHelper" , "InvalidTransactionException" , "InvalidTypeForEncoding" , "InvalidTypeForEncodingHelper" , "InvalidValue" , "InvalidValueHelper" , "InvocationEvent" , "InvocationHandler" , "InvocationTargetException" , "InvokeHandler" , "IstringHelper" , "ItalicAction" , "ItemEvent" , "ItemListener" , "ItemSelectable" , "Iterator" , "IvParameterSpec" , "JApplet" , "JButton" , "JCheckBox" , "JCheckBoxMenuItem" , "JColorChooser" , "JComboBox" , "JComponent" , "JDesktopIcon" , "JDesktopPane" , "JDialog" , "JEditorPane" , "JFileChooser" , "JFormattedTextField" , "JFrame" , "JIS" , "JInternalFrame" , "JLabel" , "JLayeredPane" , "JList" , "JMenu" , "JMenuBar" , "JMenuItem" , "JOptionPane" , "JPEGHuffmanTable" , "JPEGImageReadParam" , "JPEGImageWriteParam" , "JPEGQTable" , "JPanel" , "JPasswordField" , "JPopupMenu" , "JProgressBar" , "JRadioButton" , "JRadioButtonMenuItem" , "JRootPane" , "JScrollBar" , "JScrollPane" , "JSeparator" , "JSlider" , "JSpinner" , "JSplitPane" , "JTabbedPane" , "JTable" , "JTableHeader" , "JTextArea" , "JTextComponent" , "JTextField" , "JTextPane" , "JToggleButton" , "JToolBar" , "JToolTip" , "JTree" , "JViewport" , "JWindow" , "JarEntry" , "JarException" , "JarFile" , "JarInputStream" , "JarOutputStream" , "JarURLConnection" , "JobAttributes" , "JobHoldUntil" , "JobImpressions" , "JobImpressionsCompleted" , "JobImpressionsSupported" , "JobKOctets" , "JobKOctetsProcessed" , "JobKOctetsSupported" , "JobMediaSheets" , "JobMediaSheetsCompleted" , "JobMediaSheetsSupported" , "JobMessageFromOperator" , "JobName" , "JobOriginatingUserName" , "JobPriority" , "JobPrioritySupported" , "JobSheets" , "JobState" , "JobStateReason" , "JobStateReasons" , "KerberosKey" , "KerberosPrincipal" , "KerberosTicket" , "Kernel" , "Key" , "KeyAdapter" , "KeyAgreement" , "KeyAgreementSpi" , "KeyBinding" , "KeyEvent" , "KeyEventDispatcher" , "KeyEventPostProcessor" , "KeyException" , "KeyFactory" , "KeyFactorySpi" , "KeyGenerator" , "KeyGeneratorSpi" , "KeyListener" , "KeyManagementException" , "KeyManager" , "KeyManagerFactory" , "KeyManagerFactorySpi" , "KeyPair" , "KeyPairGenerator" , "KeyPairGeneratorSpi" , "KeySelectionManager" , "KeySpec" , "KeyStore" , "KeyStoreException" , "KeyStoreSpi" , "KeyStroke" , "KeyboardFocusManager" , "Keymap" , "LDAPCertStoreParameters" , "LIFESPAN_POLICY_ID" , "LOCATION_FORWARD" , "Label" , "LabelUI" , "LabelView" , "LanguageCallback" , "LastOwnerException" , "LayerPainter" , "LayeredHighlighter" , "LayoutFocusTraversalPolicy" , "LayoutManager" , "LayoutManager2" , "LayoutQueue" , "LazyInputMap" , "LazyValue" , "LdapContext" , "LdapReferralException" , "Lease" , "Level" , "LexicalHandler" , "LifespanPolicy" , "LifespanPolicyOperations" , "LifespanPolicyValue" , "LimitExceededException" , "Line" , "Line2D" , "LineBorder" , "LineBorderUIResource" , "LineBreakMeasurer" , "LineEvent" , "LineListener" , "LineMetrics" , "LineNumberInputStream" , "LineNumberReader" , "LineUnavailableException" , "LinkController" , "LinkException" , "LinkLoopException" , "LinkRef" , "LinkageError" , "LinkedHashMap" , "LinkedHashSet" , "LinkedList" , "List" , "ListCellRenderer" , "ListDataEvent" , "ListDataListener" , "ListEditor" , "ListIterator" , "ListModel" , "ListPainter" , "ListResourceBundle" , "ListSelectionEvent" , "ListSelectionListener" , "ListSelectionModel" , "ListUI" , "ListView" , "LoaderHandler" , "LocalObject" , "Locale" , "LocateRegistry" , "Locator" , "LocatorImpl" , "LogManager" , "LogRecord" , "LogStream" , "Logger" , "LoggingPermission" , "LoginContext" , "LoginException" , "LoginModule" , "LoginModuleControlFlag" , "Long" , "LongBuffer" , "LongHolder" , "LongLongSeqHelper" , "LongLongSeqHolder" , "LongSeqHelper" , "LongSeqHolder" , "LookAndFeel" , "LookAndFeelInfo" , "LookupOp" , "LookupTable" , "MARSHAL" , "Mac" , "MacSpi" , "MalformedInputException" , "MalformedLinkException" , "MalformedURLException" , "ManagerFactoryParameters" , "Manifest" , "Map" , "MapMode" , "MappedByteBuffer" , "MarginBorder" , "MarshalException" , "MarshalledObject" , "MaskFormatter" , "Matcher" , "Math" , "MatteBorder" , "MatteBorderUIResource" , "Media" , "MediaName" , "MediaPrintableArea" , "MediaSize" , "MediaSizeName" , "MediaTracker" , "MediaTray" , "MediaType" , "Member" , "MemoryCacheImageInputStream" , "MemoryCacheImageOutputStream" , "MemoryHandler" , "MemoryImageSource" , "Menu" , "MenuBar" , "MenuBarBorder" , "MenuBarUI" , "MenuComponent" , "MenuContainer" , "MenuDragMouseEvent" , "MenuDragMouseListener" , "MenuElement" , "MenuEvent" , "MenuItem" , "MenuItemBorder" , "MenuItemUI" , "MenuKeyEvent" , "MenuKeyListener" , "MenuListener" , "MenuSelectionManager" , "MenuShortcut" , "MessageDigest" , "MessageDigestSpi" , "MessageFormat" , "MessageProp" , "MetaEventListener" , "MetaMessage" , "MetalBorders" , "MetalButtonUI" , "MetalCheckBoxIcon" , "MetalCheckBoxUI" , "MetalComboBoxButton" , "MetalComboBoxEditor" , "MetalComboBoxIcon" , "MetalComboBoxUI" , "MetalDesktopIconUI" , "MetalFileChooserUI" , "MetalIconFactory" , "MetalInternalFrameTitlePane" , "MetalInternalFrameUI" , "MetalLabelUI" , "MetalLookAndFeel" , "MetalPopupMenuSeparatorUI" , "MetalProgressBarUI" , "MetalRadioButtonUI" , "MetalRootPaneUI" , "MetalScrollBarUI" , "MetalScrollButton" , "MetalScrollPaneUI" , "MetalSeparatorUI" , "MetalSliderUI" , "MetalSplitPaneUI" , "MetalTabbedPaneUI" , "MetalTextFieldUI" , "MetalTheme" , "MetalToggleButtonUI" , "MetalToolBarUI" , "MetalToolTipUI" , "MetalTreeUI" , "Method" , "MethodDescriptor" , "MidiChannel" , "MidiDevice" , "MidiDeviceProvider" , "MidiEvent" , "MidiFileFormat" , "MidiFileReader" , "MidiFileWriter" , "MidiMessage" , "MidiSystem" , "MidiUnavailableException" , "MimeTypeParseException" , "MinimalHTMLWriter" , "MissingResourceException" , "Mixer" , "MixerProvider" , "ModificationItem" , "Modifier" , "MouseAdapter" , "MouseDragGestureRecognizer" , "MouseEvent" , "MouseInputAdapter" , "MouseInputListener" , "MouseListener" , "MouseMotionAdapter" , "MouseMotionListener" , "MouseWheelEvent" , "MouseWheelListener" , "MultiButtonUI" , "MultiColorChooserUI" , "MultiComboBoxUI" , "MultiDesktopIconUI" , "MultiDesktopPaneUI" , "MultiDoc" , "MultiDocPrintJob" , "MultiDocPrintService" , "MultiFileChooserUI" , "MultiInternalFrameUI" , "MultiLabelUI" , "MultiListUI" , "MultiLookAndFeel" , "MultiMenuBarUI" , "MultiMenuItemUI" , "MultiOptionPaneUI" , "MultiPanelUI" , "MultiPixelPackedSampleModel" , "MultiPopupMenuUI" , "MultiProgressBarUI" , "MultiRootPaneUI" , "MultiScrollBarUI" , "MultiScrollPaneUI" , "MultiSeparatorUI" , "MultiSliderUI" , "MultiSpinnerUI" , "MultiSplitPaneUI" , "MultiTabbedPaneUI" , "MultiTableHeaderUI" , "MultiTableUI" , "MultiTextUI" , "MultiToolBarUI" , "MultiToolTipUI" , "MultiTreeUI" , "MultiViewportUI" , "MulticastSocket" , "MultipleComponentProfileHelper" , "MultipleComponentProfileHolder" , "MultipleDocumentHandling" , "MultipleDocumentHandlingType" , "MultipleMaster" , "MutableAttributeSet" , "MutableComboBoxModel" , "MutableTreeNode" , "NA" , "NO_IMPLEMENT" , "NO_MEMORY" , "NO_PERMISSION" , "NO_RESOURCES" , "NO_RESPONSE" , "NVList" , "Name" , "NameAlreadyBoundException" , "NameCallback" , "NameClassPair" , "NameComponent" , "NameComponentHelper" , "NameComponentHolder" , "NameDynAnyPair" , "NameDynAnyPairHelper" , "NameDynAnyPairSeqHelper" , "NameHelper" , "NameHolder" , "NameNotFoundException" , "NameParser" , "NameValuePair" , "NameValuePairHelper" , "NameValuePairSeqHelper" , "NamedNodeMap" , "NamedValue" , "NamespaceChangeListener" , "NamespaceSupport" , "Naming" , "NamingContext" , "NamingContextExt" , "NamingContextExtHelper" , "NamingContextExtHolder" , "NamingContextExtOperations" , "NamingContextExtPOA" , "NamingContextHelper" , "NamingContextHolder" , "NamingContextOperations" , "NamingContextPOA" , "NamingEnumeration" , "NamingEvent" , "NamingException" , "NamingExceptionEvent" , "NamingListener" , "NamingManager" , "NamingSecurityException" , "NavigationFilter" , "NegativeArraySizeException" , "NetPermission" , "NetworkInterface" , "NoClassDefFoundError" , "NoConnectionPendingException" , "NoContext" , "NoContextHelper" , "NoInitialContextException" , "NoPermissionException" , "NoRouteToHostException" , "NoServant" , "NoServantHelper" , "NoSuchAlgorithmException" , "NoSuchAttributeException" , "NoSuchElementException" , "NoSuchFieldError" , "NoSuchFieldException" , "NoSuchMethodError" , "NoSuchMethodException" , "NoSuchObjectException" , "NoSuchPaddingException" , "NoSuchProviderException" , "Node" , "NodeChangeEvent" , "NodeChangeListener" , "NodeDimensions" , "NodeList" , "NonReadableChannelException" , "NonWritableChannelException" , "NoninvertibleTransformException" , "NotActiveException" , "NotBoundException" , "NotContextException" , "NotEmpty" , "NotEmptyHelper" , "NotEmptyHolder" , "NotFound" , "NotFoundHelper" , "NotFoundHolder" , "NotFoundReason" , "NotFoundReasonHelper" , "NotFoundReasonHolder" , "NotOwnerException" , "NotSerializableException" , "NotYetBoundException" , "NotYetConnectedException" , "Notation" , "NullCipher" , "NullPointerException" , "Number" , "NumberEditor" , "NumberFormat" , "NumberFormatException" , "NumberFormatter" , "NumberOfDocuments" , "NumberOfInterveningJobs" , "NumberUp" , "NumberUpSupported" , "NumericShaper" , "OBJECT_NOT_EXIST" , "OBJ_ADAPTER" , "OMGVMCID" , "ORB" , "ORBInitInfo" , "ORBInitInfoOperations" , "ORBInitializer" , "ORBInitializerOperations" , "ObjID" , "Object" , "ObjectAlreadyActive" , "ObjectAlreadyActiveHelper" , "ObjectChangeListener" , "ObjectFactory" , "ObjectFactoryBuilder" , "ObjectHelper" , "ObjectHolder" , "ObjectIdHelper" , "ObjectImpl" , "ObjectInput" , "ObjectInputStream" , "ObjectInputValidation" , "ObjectNotActive" , "ObjectNotActiveHelper" , "ObjectOutput" , "ObjectOutputStream" , "ObjectStreamClass" , "ObjectStreamConstants" , "ObjectStreamException" , "ObjectStreamField" , "ObjectView" , "Observable" , "Observer" , "OctetSeqHelper" , "OctetSeqHolder" , "Oid" , "OpenType" , "Operation" , "OperationNotSupportedException" , "Option" , "OptionDialogBorder" , "OptionPaneUI" , "OptionalDataException" , "OrientationRequested" , "OrientationRequestedType" , "OriginType" , "Other" , "OutOfMemoryError" , "OutputDeviceAssigned" , "OutputKeys" , "OutputStream" , "OutputStreamWriter" , "OverlappingFileLockException" , "OverlayLayout" , "Owner" , "PBEKey" , "PBEKeySpec" , "PBEParameterSpec" , "PDLOverrideSupported" , "PERSIST_STORE" , "PKCS8EncodedKeySpec" , "PKIXBuilderParameters" , "PKIXCertPathBuilderResult" , "PKIXCertPathChecker" , "PKIXCertPathValidatorResult" , "PKIXParameters" , "POA" , "POAHelper" , "POAManager" , "POAManagerOperations" , "POAOperations" , "PRIVATE_MEMBER" , "PSSParameterSpec" , "PUBLIC_MEMBER" , "Package" , "PackedColorModel" , "PageAttributes" , "PageFormat" , "PageRanges" , "Pageable" , "PagesPerMinute" , "PagesPerMinuteColor" , "Paint" , "PaintContext" , "PaintEvent" , "PaletteBorder" , "PaletteCloseIcon" , "Panel" , "PanelUI" , "Paper" , "ParagraphAttribute" , "ParagraphConstants" , "ParagraphView" , "Parameter" , "ParameterBlock" , "ParameterDescriptor" , "ParameterMetaData" , "ParameterMode" , "ParameterModeHelper" , "ParameterModeHolder" , "ParseException" , "ParsePosition" , "Parser" , "ParserAdapter" , "ParserCallback" , "ParserConfigurationException" , "ParserDelegator" , "ParserFactory" , "PartialResultException" , "PasswordAuthentication" , "PasswordCallback" , "PasswordView" , "PasteAction" , "Patch" , "PathIterator" , "Pattern" , "PatternSyntaxException" , "Permission" , "PermissionCollection" , "Permissions" , "PersistenceDelegate" , "PhantomReference" , "Pipe" , "PipedInputStream" , "PipedOutputStream" , "PipedReader" , "PipedWriter" , "PixelGrabber" , "PixelInterleavedSampleModel" , "PlainDocument" , "PlainView" , "Point" , "Point2D" , "Policy" , "PolicyError" , "PolicyErrorCodeHelper" , "PolicyErrorHelper" , "PolicyErrorHolder" , "PolicyFactory" , "PolicyFactoryOperations" , "PolicyHelper" , "PolicyHolder" , "PolicyListHelper" , "PolicyListHolder" , "PolicyNode" , "PolicyOperations" , "PolicyQualifierInfo" , "PolicyTypeHelper" , "Polygon" , "PooledConnection" , "Popup" , "PopupFactory" , "PopupMenu" , "PopupMenuBorder" , "PopupMenuEvent" , "PopupMenuListener" , "PopupMenuUI" , "Port" , "PortUnreachableException" , "PortableRemoteObject" , "PortableRemoteObjectDelegate" , "Position" , "PreferenceChangeEvent" , "PreferenceChangeListener" , "Preferences" , "PreferencesFactory" , "PreparedStatement" , "PresentationDirection" , "Principal" , "PrincipalHolder" , "PrintEvent" , "PrintException" , "PrintGraphics" , "PrintJob" , "PrintJobAdapter" , "PrintJobAttribute" , "PrintJobAttributeEvent" , "PrintJobAttributeListener" , "PrintJobAttributeSet" , "PrintJobEvent" , "PrintJobListener" , "PrintQuality" , "PrintQualityType" , "PrintRequestAttribute" , "PrintRequestAttributeSet" , "PrintService" , "PrintServiceAttribute" , "PrintServiceAttributeEvent" , "PrintServiceAttributeListener" , "PrintServiceAttributeSet" , "PrintServiceLookup" , "PrintStream" , "PrintWriter" , "Printable" , "PrinterAbortException" , "PrinterException" , "PrinterGraphics" , "PrinterIOException" , "PrinterInfo" , "PrinterIsAcceptingJobs" , "PrinterJob" , "PrinterLocation" , "PrinterMakeAndModel" , "PrinterMessageFromOperator" , "PrinterMoreInfo" , "PrinterMoreInfoManufacturer" , "PrinterName" , "PrinterResolution" , "PrinterState" , "PrinterStateReason" , "PrinterStateReasons" , "PrinterURI" , "PrivateCredentialPermission" , "PrivateKey" , "PrivilegedAction" , "PrivilegedActionException" , "PrivilegedExceptionAction" , "Process" , "ProcessingInstruction" , "ProfileDataException" , "ProfileIdHelper" , "ProgressBarUI" , "ProgressMonitor" , "ProgressMonitorInputStream" , "Properties" , "PropertyChangeEvent" , "PropertyChangeListener" , "PropertyChangeListenerProxy" , "PropertyChangeSupport" , "PropertyDescriptor" , "PropertyEditor" , "PropertyEditorManager" , "PropertyEditorSupport" , "PropertyPermission" , "PropertyResourceBundle" , "PropertyVetoException" , "ProtectionDomain" , "ProtocolException" , "Provider" , "ProviderException" , "Proxy" , "ProxyLazyValue" , "PublicKey" , "PushbackInputStream" , "PushbackReader" , "PutField" , "QuadCurve2D" , "QueuedJobCount" , "RC2ParameterSpec" , "RC5ParameterSpec" , "READER" , "REQUEST_PROCESSING_POLICY_ID" , "RGBImageFilter" , "RMIClassLoader" , "RMIClassLoaderSpi" , "RMIClientSocketFactory" , "RMIFailureHandler" , "RMISecurityException" , "RMISecurityManager" , "RMIServerSocketFactory" , "RMISocketFactory" , "RSAKey" , "RSAKeyGenParameterSpec" , "RSAMultiPrimePrivateCrtKey" , "RSAMultiPrimePrivateCrtKeySpec" , "RSAOtherPrimeInfo" , "RSAPrivateCrtKey" , "RSAPrivateCrtKeySpec" , "RSAPrivateKey" , "RSAPrivateKeySpec" , "RSAPublicKey" , "RSAPublicKeySpec" , "RTFEditorKit" , "RadioButtonBorder" , "Random" , "RandomAccess" , "RandomAccessFile" , "Raster" , "RasterFormatException" , "RasterOp" , "ReadOnlyBufferException" , "ReadableByteChannel" , "Reader" , "Receiver" , "Rectangle" , "Rectangle2D" , "RectangularShape" , "Ref" , "RefAddr" , "Reference" , "ReferenceQueue" , "ReferenceUriSchemesSupported" , "Referenceable" , "ReferralException" , "ReflectPermission" , "RefreshFailedException" , "Refreshable" , "RegisterableService" , "Registry" , "RegistryHandler" , "RemarshalException" , "Remote" , "RemoteCall" , "RemoteException" , "RemoteObject" , "RemoteRef" , "RemoteServer" , "RemoteStub" , "RenderContext" , "RenderableImage" , "RenderableImageOp" , "RenderableImageProducer" , "RenderedImage" , "RenderedImageFactory" , "Renderer" , "RenderingHints" , "RepaintManager" , "ReplicateScaleFilter" , "RepositoryIdHelper" , "Request" , "RequestInfo" , "RequestInfoOperations" , "RequestProcessingPolicy" , "RequestProcessingPolicyOperations" , "RequestProcessingPolicyValue" , "RequestingUserName" , "RescaleOp" , "ResolutionSyntax" , "ResolveResult" , "Resolver" , "ResourceBundle" , "ResponseHandler" , "Result" , "ResultSet" , "ResultSetMetaData" , "ReverbType" , "Robot" , "RolloverButtonBorder" , "RootPaneContainer" , "RootPaneUI" , "RoundRectangle2D" , "RowMapper" , "RowSet" , "RowSetEvent" , "RowSetInternal" , "RowSetListener" , "RowSetMetaData" , "RowSetReader" , "RowSetWriter" , "RuleBasedCollator" , "RunTime" , "RunTimeOperations" , "Runnable" , "Runtime" , "RuntimeException" , "RuntimePermission" , "SAXException" , "SAXNotRecognizedException" , "SAXNotSupportedException" , "SAXParseException" , "SAXParser" , "SAXParserFactory" , "SAXResult" , "SAXSource" , "SAXTransformerFactory" , "SERVANT_RETENTION_POLICY_ID" , "SERVICE_FORMATTED" , "SQLData" , "SQLException" , "SQLInput" , "SQLOutput" , "SQLPermission" , "SQLWarning" , "SSLContext" , "SSLContextSpi" , "SSLException" , "SSLHandshakeException" , "SSLKeyException" , "SSLPeerUnverifiedException" , "SSLPermission" , "SSLProtocolException" , "SSLServerSocket" , "SSLServerSocketFactory" , "SSLSession" , "SSLSessionBindingEvent" , "SSLSessionBindingListener" , "SSLSessionContext" , "SSLSocket" , "SSLSocketFactory" , "STRING" , "SUCCESSFUL" , "SYNC_WITH_TRANSPORT" , "SYSTEM_EXCEPTION" , "SampleModel" , "Savepoint" , "ScatteringByteChannel" , "SchemaViolationException" , "ScrollBarUI" , "ScrollPane" , "ScrollPaneAdjustable" , "ScrollPaneBorder" , "ScrollPaneConstants" , "ScrollPaneLayout" , "ScrollPaneUI" , "Scrollable" , "Scrollbar" , "SealedObject" , "SearchControls" , "SearchResult" , "SecretKey" , "SecretKeyFactory" , "SecretKeyFactorySpi" , "SecretKeySpec" , "SecureClassLoader" , "SecureRandom" , "SecureRandomSpi" , "Security" , "SecurityException" , "SecurityManager" , "SecurityPermission" , "Segment" , "SelectableChannel" , "SelectionKey" , "Selector" , "SelectorProvider" , "Separator" , "SeparatorUI" , "Sequence" , "SequenceInputStream" , "Sequencer" , "Serializable" , "SerializablePermission" , "Servant" , "ServantActivator" , "ServantActivatorHelper" , "ServantActivatorOperations" , "ServantActivatorPOA" , "ServantAlreadyActive" , "ServantAlreadyActiveHelper" , "ServantLocator" , "ServantLocatorHelper" , "ServantLocatorOperations" , "ServantLocatorPOA" , "ServantManager" , "ServantManagerOperations" , "ServantNotActive" , "ServantNotActiveHelper" , "ServantObject" , "ServantRetentionPolicy" , "ServantRetentionPolicyOperations" , "ServantRetentionPolicyValue" , "ServerCloneException" , "ServerError" , "ServerException" , "ServerNotActiveException" , "ServerRef" , "ServerRequest" , "ServerRequestInfo" , "ServerRequestInfoOperations" , "ServerRequestInterceptor" , "ServerRequestInterceptorOperations" , "ServerRuntimeException" , "ServerSocket" , "ServerSocketChannel" , "ServerSocketFactory" , "ServiceContext" , "ServiceContextHelper" , "ServiceContextHolder" , "ServiceContextListHelper" , "ServiceContextListHolder" , "ServiceDetail" , "ServiceDetailHelper" , "ServiceIdHelper" , "ServiceInformation" , "ServiceInformationHelper" , "ServiceInformationHolder" , "ServicePermission" , "ServiceRegistry" , "ServiceUI" , "ServiceUIFactory" , "ServiceUnavailableException" , "Set" , "SetOfIntegerSyntax" , "SetOverrideType" , "SetOverrideTypeHelper" , "Severity" , "Shape" , "ShapeGraphicAttribute" , "SheetCollate" , "Short" , "ShortBuffer" , "ShortBufferException" , "ShortHolder" , "ShortLookupTable" , "ShortMessage" , "ShortSeqHelper" , "ShortSeqHolder" , "Sides" , "SidesType" , "Signature" , "SignatureException" , "SignatureSpi" , "SignedObject" , "Signer" , "SimpleAttributeSet" , "SimpleBeanInfo" , "SimpleDateFormat" , "SimpleDoc" , "SimpleFormatter" , "SimpleTimeZone" , "SinglePixelPackedSampleModel" , "SingleSelectionModel" , "SinkChannel" , "Size2DSyntax" , "SizeLimitExceededException" , "SizeRequirements" , "SizeSequence" , "Skeleton" , "SkeletonMismatchException" , "SkeletonNotFoundException" , "SliderUI" , "Socket" , "SocketAddress" , "SocketChannel" , "SocketException" , "SocketFactory" , "SocketHandler" , "SocketImpl" , "SocketImplFactory" , "SocketOptions" , "SocketPermission" , "SocketSecurityException" , "SocketTimeoutException" , "SoftBevelBorder" , "SoftReference" , "SortedMap" , "SortedSet" , "SortingFocusTraversalPolicy" , "Soundbank" , "SoundbankReader" , "SoundbankResource" , "Source" , "SourceChannel" , "SourceDataLine" , "SourceLocator" , "SpinnerDateModel" , "SpinnerListModel" , "SpinnerModel" , "SpinnerNumberModel" , "SpinnerUI" , "SplitPaneBorder" , "SplitPaneUI" , "Spring" , "SpringLayout" , "Stack" , "StackOverflowError" , "StackTraceElement" , "StartTlsRequest" , "StartTlsResponse" , "State" , "StateEdit" , "StateEditable" , "StateFactory" , "Statement" , "StreamCorruptedException" , "StreamHandler" , "StreamPrintService" , "StreamPrintServiceFactory" , "StreamResult" , "StreamSource" , "StreamTokenizer" , "Streamable" , "StreamableValue" , "StrictMath" , "String" , "StringBuffer" , "StringBufferInputStream" , "StringCharacterIterator" , "StringContent" , "StringHolder" , "StringIndexOutOfBoundsException" , "StringNameHelper" , "StringReader" , "StringRefAddr" , "StringSelection" , "StringSeqHelper" , "StringSeqHolder" , "StringTokenizer" , "StringValueHelper" , "StringWriter" , "Stroke" , "Struct" , "StructMember" , "StructMemberHelper" , "Stub" , "StubDelegate" , "StubNotFoundException" , "Style" , "StyleConstants" , "StyleContext" , "StyleSheet" , "StyledDocument" , "StyledEditorKit" , "StyledTextAction" , "Subject" , "SubjectDomainCombiner" , "Subset" , "SupportedValuesAttribute" , "SwingConstants" , "SwingPropertyChangeSupport" , "SwingUtilities" , "SyncFailedException" , "SyncMode" , "SyncScopeHelper" , "Synthesizer" , "SysexMessage" , "System" , "SystemColor" , "SystemException" , "SystemFlavorMap" , "TAG_ALTERNATE_IIOP_ADDRESS" , "TAG_CODE_SETS" , "TAG_INTERNET_IOP" , "TAG_JAVA_CODEBASE" , "TAG_MULTIPLE_COMPONENTS" , "TAG_ORB_TYPE" , "TAG_POLICIES" , "TCKind" , "THREAD_POLICY_ID" , "TRANSACTION_REQUIRED" , "TRANSACTION_ROLLEDBACK" , "TRANSIENT" , "TRANSPORT_RETRY" , "TabExpander" , "TabSet" , "TabStop" , "TabableView" , "TabbedPaneUI" , "TableCellEditor" , "TableCellRenderer" , "TableColumn" , "TableColumnModel" , "TableColumnModelEvent" , "TableColumnModelListener" , "TableHeaderBorder" , "TableHeaderUI" , "TableModel" , "TableModelEvent" , "TableModelListener" , "TableUI" , "TableView" , "Tag" , "TagElement" , "TaggedComponent" , "TaggedComponentHelper" , "TaggedComponentHolder" , "TaggedProfile" , "TaggedProfileHelper" , "TaggedProfileHolder" , "TargetDataLine" , "Templates" , "TemplatesHandler" , "Text" , "TextAction" , "TextArea" , "TextAttribute" , "TextComponent" , "TextEvent" , "TextField" , "TextFieldBorder" , "TextHitInfo" , "TextInputCallback" , "TextLayout" , "TextListener" , "TextMeasurer" , "TextOutputCallback" , "TextSyntax" , "TextUI" , "TexturePaint" , "Thread" , "ThreadDeath" , "ThreadGroup" , "ThreadLocal" , "ThreadPolicy" , "ThreadPolicyOperations" , "ThreadPolicyValue" , "Throwable" , "Tie" , "TileObserver" , "Time" , "TimeLimitExceededException" , "TimeZone" , "Timer" , "TimerTask" , "Timestamp" , "TitledBorder" , "TitledBorderUIResource" , "ToggleButtonBorder" , "ToggleButtonModel" , "TooManyListenersException" , "ToolBarBorder" , "ToolBarUI" , "ToolTipManager" , "ToolTipUI" , "Toolkit" , "Track" , "TransactionRequiredException" , "TransactionRolledbackException" , "TransactionService" , "TransferHandler" , "Transferable" , "TransformAttribute" , "Transformer" , "TransformerConfigurationException" , "TransformerException" , "TransformerFactory" , "TransformerFactoryConfigurationError" , "TransformerHandler" , "Transmitter" , "Transparency" , "TreeCellEditor" , "TreeCellRenderer" , "TreeControlIcon" , "TreeExpansionEvent" , "TreeExpansionListener" , "TreeFolderIcon" , "TreeLeafIcon" , "TreeMap" , "TreeModel" , "TreeModelEvent" , "TreeModelListener" , "TreeNode" , "TreePath" , "TreeSelectionEvent" , "TreeSelectionListener" , "TreeSelectionModel" , "TreeSet" , "TreeUI" , "TreeWillExpandListener" , "TrustAnchor" , "TrustManager" , "TrustManagerFactory" , "TrustManagerFactorySpi" , "Type" , "TypeCode" , "TypeCodeHolder" , "TypeMismatch" , "TypeMismatchHelper" , "Types" , "UID" , "UIDefaults" , "UIManager" , "UIResource" , "ULongLongSeqHelper" , "ULongLongSeqHolder" , "ULongSeqHelper" , "ULongSeqHolder" , "UNKNOWN" , "UNSUPPORTED_POLICY" , "UNSUPPORTED_POLICY_VALUE" , "URI" , "URIException" , "URIResolver" , "URISyntax" , "URISyntaxException" , "URL" , "URLClassLoader" , "URLConnection" , "URLDecoder" , "URLEncoder" , "URLStreamHandler" , "URLStreamHandlerFactory" , "URLStringHelper" , "USER_EXCEPTION" , "UShortSeqHelper" , "UShortSeqHolder" , "UTFDataFormatException" , "UndeclaredThrowableException" , "UnderlineAction" , "UndoManager" , "UndoableEdit" , "UndoableEditEvent" , "UndoableEditListener" , "UndoableEditSupport" , "UnexpectedException" , "UnicastRemoteObject" , "UnicodeBlock" , "UnionMember" , "UnionMemberHelper" , "UnknownEncoding" , "UnknownEncodingHelper" , "UnknownError" , "UnknownException" , "UnknownGroupException" , "UnknownHostException" , "UnknownObjectException" , "UnknownServiceException" , "UnknownTag" , "UnknownUserException" , "UnknownUserExceptionHelper" , "UnknownUserExceptionHolder" , "UnmappableCharacterException" , "UnmarshalException" , "UnmodifiableSetException" , "UnrecoverableKeyException" , "Unreferenced" , "UnresolvedAddressException" , "UnresolvedPermission" , "UnsatisfiedLinkError" , "UnsolicitedNotification" , "UnsolicitedNotificationEvent" , "UnsolicitedNotificationListener" , "UnsupportedAddressTypeException" , "UnsupportedAudioFileException" , "UnsupportedCallbackException" , "UnsupportedCharsetException" , "UnsupportedClassVersionError" , "UnsupportedEncodingException" , "UnsupportedFlavorException" , "UnsupportedLookAndFeelException" , "UnsupportedOperationException" , "UserException" , "Util" , "UtilDelegate" , "Utilities" , "VMID" , "VM_ABSTRACT" , "VM_CUSTOM" , "VM_NONE" , "VM_TRUNCATABLE" , "ValueBase" , "ValueBaseHelper" , "ValueBaseHolder" , "ValueFactory" , "ValueHandler" , "ValueMember" , "ValueMemberHelper" , "VariableHeightLayoutCache" , "Vector" , "VerifyError" , "VersionSpecHelper" , "VetoableChangeListener" , "VetoableChangeListenerProxy" , "VetoableChangeSupport" , "View" , "ViewFactory" , "ViewportLayout" , "ViewportUI" , "VirtualMachineError" , "Visibility" , "VisibilityHelper" , "VoiceStatus" , "Void" , "VolatileImage" , "WCharSeqHelper" , "WCharSeqHolder" , "WStringSeqHelper" , "WStringSeqHolder" , "WStringValueHelper" , "WeakHashMap" , "WeakReference" , "Window" , "WindowAdapter" , "WindowConstants" , "WindowEvent" , "WindowFocusListener" , "WindowListener" , "WindowStateListener" , "WrappedPlainView" , "WritableByteChannel" , "WritableRaster" , "WritableRenderedImage" , "WriteAbortedException" , "Writer" , "WrongAdapter" , "WrongAdapterHelper" , "WrongPolicy" , "WrongPolicyHelper" , "WrongTransaction" , "WrongTransactionHelper" , "WrongTransactionHolder" , "X500Principal" , "X500PrivateCredential" , "X509CRL" , "X509CRLEntry" , "X509CRLSelector" , "X509CertSelector" , "X509Certificate" , "X509EncodedKeySpec" , "X509Extension" , "X509KeyManager" , "X509TrustManager" , "XAConnection" , "XADataSource" , "XAException" , "XAResource" , "XMLDecoder" , "XMLEncoder" , "XMLFilter" , "XMLFilterImpl" , "XMLFormatter" , "XMLReader" , "XMLReaderAdapter" , "XMLReaderFactory" , "Xid" , "ZipEntry" , "ZipException" , "ZipFile" , "ZipInputStream" , "ZipOutputStream" , "ZoneView" , "_BindingIteratorImplBase" , "_BindingIteratorStub" , "_DynAnyFactoryStub" , "_DynAnyStub" , "_DynArrayStub" , "_DynEnumStub" , "_DynFixedStub" , "_DynSequenceStub" , "_DynStructStub" , "_DynUnionStub" , "_DynValueStub" , "_IDLTypeStub" , "_NamingContextExtStub" , "_NamingContextImplBase" , "_NamingContextStub" , "_PolicyStub" , "_Remote_Stub" , "_ServantActivatorStub" , "_ServantLocatorStub" ]) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Float , rAttribute = FloatTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [ Rule { rMatcher = AnyChar "fF" , rAttribute = FloatTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCOct , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCHex , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [ Rule { rMatcher = StringDetect "ULL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LUL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LLU" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "UL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LU" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "U" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "L" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCChar , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Java String" ) ] } , Rule { rMatcher = AnyChar "!%&()+,-<=>?[]^{|}~" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Scriptlet" , Context { cName = "Jsp Scriptlet" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = Detect2Chars '%' '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "<\\s*jsp:(declaration|expression|scriptlet)\\s*>" , reCompiled = Just (compileRegex False "<\\s*jsp:(declaration|expression|scriptlet)\\s*>") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "abstract" , "assert" , "break" , "case" , "catch" , "class" , "continue" , "default" , "do" , "else" , "extends" , "false" , "finally" , "for" , "goto" , "if" , "implements" , "import" , "instanceof" , "interface" , "native" , "new" , "null" , "package" , "private" , "protected" , "public" , "return" , "strictfp" , "super" , "switch" , "synchronized" , "this" , "throw" , "throws" , "transient" , "true" , "try" , "volatile" , "while" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "and" , "div" , "empty" , "eq" , "false" , "ge" , "gt" , "instanceof" , "le" , "lt" , "mod" , "ne" , "not" , "null" , "or" , "true" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "boolean" , "byte" , "char" , "const" , "double" , "final" , "float" , "int" , "long" , "short" , "static" , "void" ]) , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "ARG_IN" , "ARG_INOUT" , "ARG_OUT" , "AWTError" , "AWTEvent" , "AWTEventListener" , "AWTEventListenerProxy" , "AWTEventMulticaster" , "AWTException" , "AWTKeyStroke" , "AWTPermission" , "AbstractAction" , "AbstractBorder" , "AbstractButton" , "AbstractCellEditor" , "AbstractCollection" , "AbstractColorChooserPanel" , "AbstractDocument" , "AbstractFormatter" , "AbstractFormatterFactory" , "AbstractInterruptibleChannel" , "AbstractLayoutCache" , "AbstractList" , "AbstractListModel" , "AbstractMap" , "AbstractMethodError" , "AbstractPreferences" , "AbstractSelectableChannel" , "AbstractSelectionKey" , "AbstractSelector" , "AbstractSequentialList" , "AbstractSet" , "AbstractSpinnerModel" , "AbstractTableModel" , "AbstractUndoableEdit" , "AbstractWriter" , "AccessControlContext" , "AccessControlException" , "AccessController" , "AccessException" , "Accessible" , "AccessibleAction" , "AccessibleBundle" , "AccessibleComponent" , "AccessibleContext" , "AccessibleEditableText" , "AccessibleExtendedComponent" , "AccessibleExtendedTable" , "AccessibleHyperlink" , "AccessibleHypertext" , "AccessibleIcon" , "AccessibleKeyBinding" , "AccessibleObject" , "AccessibleRelation" , "AccessibleRelationSet" , "AccessibleResourceBundle" , "AccessibleRole" , "AccessibleSelection" , "AccessibleState" , "AccessibleStateSet" , "AccessibleTable" , "AccessibleTableModelChange" , "AccessibleText" , "AccessibleValue" , "AccountExpiredException" , "Acl" , "AclEntry" , "AclNotFoundException" , "Action" , "ActionEvent" , "ActionListener" , "ActionMap" , "ActionMapUIResource" , "Activatable" , "ActivateFailedException" , "ActivationDesc" , "ActivationException" , "ActivationGroup" , "ActivationGroupDesc" , "ActivationGroupID" , "ActivationGroup_Stub" , "ActivationID" , "ActivationInstantiator" , "ActivationMonitor" , "ActivationSystem" , "Activator" , "ActiveEvent" , "ActiveValue" , "AdapterActivator" , "AdapterActivatorOperations" , "AdapterAlreadyExists" , "AdapterAlreadyExistsHelper" , "AdapterInactive" , "AdapterInactiveHelper" , "AdapterNonExistent" , "AdapterNonExistentHelper" , "AddressHelper" , "Adjustable" , "AdjustmentEvent" , "AdjustmentListener" , "Adler32" , "AffineTransform" , "AffineTransformOp" , "AlgorithmParameterGenerator" , "AlgorithmParameterGeneratorSpi" , "AlgorithmParameterSpec" , "AlgorithmParameters" , "AlgorithmParametersSpi" , "AlignmentAction" , "AllPermission" , "AlphaComposite" , "AlreadyBound" , "AlreadyBoundException" , "AlreadyBoundHelper" , "AlreadyBoundHolder" , "AlreadyConnectedException" , "AncestorEvent" , "AncestorListener" , "Annotation" , "Any" , "AnyHolder" , "AnySeqHelper" , "AnySeqHolder" , "AppConfigurationEntry" , "Applet" , "AppletContext" , "AppletInitializer" , "AppletStub" , "ApplicationException" , "Arc2D" , "Area" , "AreaAveragingScaleFilter" , "ArithmeticException" , "Array" , "ArrayIndexOutOfBoundsException" , "ArrayList" , "ArrayStoreException" , "Arrays" , "AssertionError" , "AsyncBoxView" , "AsynchronousCloseException" , "Attr" , "Attribute" , "AttributeContext" , "AttributeException" , "AttributeInUseException" , "AttributeList" , "AttributeListImpl" , "AttributeModificationException" , "AttributeSet" , "AttributeSetUtilities" , "AttributeUndoableEdit" , "AttributedCharacterIterator" , "AttributedString" , "Attributes" , "AttributesImpl" , "AudioClip" , "AudioFileFormat" , "AudioFileReader" , "AudioFileWriter" , "AudioFormat" , "AudioInputStream" , "AudioPermission" , "AudioSystem" , "AuthPermission" , "AuthenticationException" , "AuthenticationNotSupportedException" , "Authenticator" , "Autoscroll" , "BAD_CONTEXT" , "BAD_INV_ORDER" , "BAD_OPERATION" , "BAD_PARAM" , "BAD_POLICY" , "BAD_POLICY_TYPE" , "BAD_POLICY_VALUE" , "BAD_TYPECODE" , "BCSIterator" , "BCSSServiceProvider" , "BYTE_ARRAY" , "BackingStoreException" , "BadKind" , "BadLocationException" , "BadPaddingException" , "BandCombineOp" , "BandedSampleModel" , "BasicArrowButton" , "BasicAttribute" , "BasicAttributes" , "BasicBorders" , "BasicButtonListener" , "BasicButtonUI" , "BasicCaret" , "BasicCheckBoxMenuItemUI" , "BasicCheckBoxUI" , "BasicColorChooserUI" , "BasicComboBoxEditor" , "BasicComboBoxRenderer" , "BasicComboBoxUI" , "BasicComboPopup" , "BasicDesktopIconUI" , "BasicDesktopPaneUI" , "BasicDirectoryModel" , "BasicEditorPaneUI" , "BasicFileChooserUI" , "BasicFormattedTextFieldUI" , "BasicGraphicsUtils" , "BasicHTML" , "BasicHighlighter" , "BasicIconFactory" , "BasicInternalFrameTitlePane" , "BasicInternalFrameUI" , "BasicLabelUI" , "BasicListUI" , "BasicLookAndFeel" , "BasicMenuBarUI" , "BasicMenuItemUI" , "BasicMenuUI" , "BasicOptionPaneUI" , "BasicPanelUI" , "BasicPasswordFieldUI" , "BasicPermission" , "BasicPopupMenuSeparatorUI" , "BasicPopupMenuUI" , "BasicProgressBarUI" , "BasicRadioButtonMenuItemUI" , "BasicRadioButtonUI" , "BasicRootPaneUI" , "BasicScrollBarUI" , "BasicScrollPaneUI" , "BasicSeparatorUI" , "BasicSliderUI" , "BasicSpinnerUI" , "BasicSplitPaneDivider" , "BasicSplitPaneUI" , "BasicStroke" , "BasicTabbedPaneUI" , "BasicTableHeaderUI" , "BasicTableUI" , "BasicTextAreaUI" , "BasicTextFieldUI" , "BasicTextPaneUI" , "BasicTextUI" , "BasicToggleButtonUI" , "BasicToolBarSeparatorUI" , "BasicToolBarUI" , "BasicToolTipUI" , "BasicTreeUI" , "BasicViewportUI" , "BatchUpdateException" , "BeanContext" , "BeanContextChild" , "BeanContextChildComponentProxy" , "BeanContextChildSupport" , "BeanContextContainerProxy" , "BeanContextEvent" , "BeanContextMembershipEvent" , "BeanContextMembershipListener" , "BeanContextProxy" , "BeanContextServiceAvailableEvent" , "BeanContextServiceProvider" , "BeanContextServiceProviderBeanInfo" , "BeanContextServiceRevokedEvent" , "BeanContextServiceRevokedListener" , "BeanContextServices" , "BeanContextServicesListener" , "BeanContextServicesSupport" , "BeanContextSupport" , "BeanDescriptor" , "BeanInfo" , "Beans" , "BeepAction" , "BevelBorder" , "BevelBorderUIResource" , "Bias" , "Bidi" , "BigDecimal" , "BigInteger" , "BinaryRefAddr" , "BindException" , "Binding" , "BindingHelper" , "BindingHolder" , "BindingIterator" , "BindingIteratorHelper" , "BindingIteratorHolder" , "BindingIteratorOperations" , "BindingIteratorPOA" , "BindingListHelper" , "BindingListHolder" , "BindingType" , "BindingTypeHelper" , "BindingTypeHolder" , "BitSet" , "Blob" , "BlockView" , "BoldAction" , "Book" , "Boolean" , "BooleanControl" , "BooleanHolder" , "BooleanSeqHelper" , "BooleanSeqHolder" , "Border" , "BorderFactory" , "BorderLayout" , "BorderUIResource" , "BoundedRangeModel" , "Bounds" , "Box" , "BoxLayout" , "BoxPainter" , "BoxView" , "BoxedValueHelper" , "BreakIterator" , "Buffer" , "BufferCapabilities" , "BufferOverflowException" , "BufferStrategy" , "BufferUnderflowException" , "BufferedImage" , "BufferedImageFilter" , "BufferedImageOp" , "BufferedInputStream" , "BufferedOutputStream" , "BufferedReader" , "BufferedWriter" , "Button" , "ButtonAreaLayout" , "ButtonBorder" , "ButtonGroup" , "ButtonModel" , "ButtonUI" , "Byte" , "ByteArrayInputStream" , "ByteArrayOutputStream" , "ByteBuffer" , "ByteChannel" , "ByteHolder" , "ByteLookupTable" , "ByteOrder" , "CDATASection" , "CHAR_ARRAY" , "CMMException" , "COMM_FAILURE" , "CRC32" , "CRL" , "CRLException" , "CRLSelector" , "CSS" , "CTX_RESTRICT_SCOPE" , "Calendar" , "CallableStatement" , "Callback" , "CallbackHandler" , "CancelablePrintJob" , "CancelledKeyException" , "CannotProceed" , "CannotProceedException" , "CannotProceedHelper" , "CannotProceedHolder" , "CannotRedoException" , "CannotUndoException" , "Canvas" , "CardLayout" , "Caret" , "CaretEvent" , "CaretListener" , "CaretPolicy" , "CellEditor" , "CellEditorListener" , "CellRendererPane" , "CertPath" , "CertPathBuilder" , "CertPathBuilderException" , "CertPathBuilderResult" , "CertPathBuilderSpi" , "CertPathParameters" , "CertPathRep" , "CertPathValidator" , "CertPathValidatorException" , "CertPathValidatorResult" , "CertPathValidatorSpi" , "CertSelector" , "CertStore" , "CertStoreException" , "CertStoreParameters" , "CertStoreSpi" , "Certificate" , "CertificateEncodingException" , "CertificateException" , "CertificateExpiredException" , "CertificateFactory" , "CertificateFactorySpi" , "CertificateNotYetValidException" , "CertificateParsingException" , "CertificateRep" , "ChangeEvent" , "ChangeListener" , "ChangedCharSetException" , "Channel" , "ChannelBinding" , "Channels" , "CharArrayReader" , "CharArrayWriter" , "CharBuffer" , "CharConversionException" , "CharHolder" , "CharSeqHelper" , "CharSeqHolder" , "CharSequence" , "Character" , "CharacterAttribute" , "CharacterCodingException" , "CharacterConstants" , "CharacterData" , "CharacterIterator" , "Charset" , "CharsetDecoder" , "CharsetEncoder" , "CharsetProvider" , "Checkbox" , "CheckboxGroup" , "CheckboxMenuItem" , "CheckedInputStream" , "CheckedOutputStream" , "Checksum" , "Choice" , "ChoiceCallback" , "ChoiceFormat" , "Chromaticity" , "Cipher" , "CipherInputStream" , "CipherOutputStream" , "CipherSpi" , "Class" , "ClassCastException" , "ClassCircularityError" , "ClassDesc" , "ClassFormatError" , "ClassLoader" , "ClassNotFoundException" , "ClientRequestInfo" , "ClientRequestInfoOperations" , "ClientRequestInterceptor" , "ClientRequestInterceptorOperations" , "Clip" , "Clipboard" , "ClipboardOwner" , "Clob" , "CloneNotSupportedException" , "Cloneable" , "ClosedByInterruptException" , "ClosedChannelException" , "ClosedSelectorException" , "CodeSets" , "CodeSource" , "Codec" , "CodecFactory" , "CodecFactoryHelper" , "CodecFactoryOperations" , "CodecOperations" , "CoderMalfunctionError" , "CoderResult" , "CodingErrorAction" , "CollationElementIterator" , "CollationKey" , "Collator" , "Collection" , "CollectionCertStoreParameters" , "Collections" , "Color" , "ColorAttribute" , "ColorChooserComponentFactory" , "ColorChooserUI" , "ColorConstants" , "ColorConvertOp" , "ColorModel" , "ColorSelectionModel" , "ColorSpace" , "ColorSupported" , "ColorType" , "ColorUIResource" , "ComboBoxEditor" , "ComboBoxModel" , "ComboBoxUI" , "ComboPopup" , "CommandEnvironment" , "Comment" , "CommunicationException" , "Comparable" , "Comparator" , "Compiler" , "CompletionStatus" , "CompletionStatusHelper" , "Component" , "ComponentAdapter" , "ComponentColorModel" , "ComponentEvent" , "ComponentIdHelper" , "ComponentInputMap" , "ComponentInputMapUIResource" , "ComponentListener" , "ComponentOrientation" , "ComponentSampleModel" , "ComponentUI" , "ComponentView" , "Composite" , "CompositeContext" , "CompositeName" , "CompositeView" , "CompoundBorder" , "CompoundBorderUIResource" , "CompoundControl" , "CompoundEdit" , "CompoundName" , "Compression" , "ConcurrentModificationException" , "Configuration" , "ConfigurationException" , "ConfirmationCallback" , "ConnectException" , "ConnectIOException" , "Connection" , "ConnectionEvent" , "ConnectionEventListener" , "ConnectionPendingException" , "ConnectionPoolDataSource" , "ConsoleHandler" , "Constraints" , "Constructor" , "Container" , "ContainerAdapter" , "ContainerEvent" , "ContainerListener" , "ContainerOrderFocusTraversalPolicy" , "Content" , "ContentHandler" , "ContentHandlerFactory" , "ContentModel" , "Context" , "ContextList" , "ContextNotEmptyException" , "ContextualRenderedImageFactory" , "Control" , "ControlFactory" , "ControllerEventListener" , "ConvolveOp" , "CookieHolder" , "Copies" , "CopiesSupported" , "CopyAction" , "CredentialExpiredException" , "CropImageFilter" , "CubicCurve2D" , "Currency" , "Current" , "CurrentHelper" , "CurrentHolder" , "CurrentOperations" , "Cursor" , "CustomMarshal" , "CustomValue" , "Customizer" , "CutAction" , "DATA_CONVERSION" , "DESKeySpec" , "DESedeKeySpec" , "DGC" , "DHGenParameterSpec" , "DHKey" , "DHParameterSpec" , "DHPrivateKey" , "DHPrivateKeySpec" , "DHPublicKey" , "DHPublicKeySpec" , "DOMException" , "DOMImplementation" , "DOMLocator" , "DOMResult" , "DOMSource" , "DSAKey" , "DSAKeyPairGenerator" , "DSAParameterSpec" , "DSAParams" , "DSAPrivateKey" , "DSAPrivateKeySpec" , "DSAPublicKey" , "DSAPublicKeySpec" , "DTD" , "DTDConstants" , "DTDHandler" , "DataBuffer" , "DataBufferByte" , "DataBufferDouble" , "DataBufferFloat" , "DataBufferInt" , "DataBufferShort" , "DataBufferUShort" , "DataFlavor" , "DataFormatException" , "DataInput" , "DataInputStream" , "DataLine" , "DataOutput" , "DataOutputStream" , "DataSource" , "DataTruncation" , "DatabaseMetaData" , "DatagramChannel" , "DatagramPacket" , "DatagramSocket" , "DatagramSocketImpl" , "DatagramSocketImplFactory" , "Date" , "DateEditor" , "DateFormat" , "DateFormatSymbols" , "DateFormatter" , "DateTimeAtCompleted" , "DateTimeAtCreation" , "DateTimeAtProcessing" , "DateTimeSyntax" , "DebugGraphics" , "DecimalFormat" , "DecimalFormatSymbols" , "DeclHandler" , "DefaultBoundedRangeModel" , "DefaultButtonModel" , "DefaultCaret" , "DefaultCellEditor" , "DefaultColorSelectionModel" , "DefaultComboBoxModel" , "DefaultDesktopManager" , "DefaultEditor" , "DefaultEditorKit" , "DefaultFocusManager" , "DefaultFocusTraversalPolicy" , "DefaultFormatter" , "DefaultFormatterFactory" , "DefaultHandler" , "DefaultHighlightPainter" , "DefaultHighlighter" , "DefaultKeyTypedAction" , "DefaultKeyboardFocusManager" , "DefaultListCellRenderer" , "DefaultListModel" , "DefaultListSelectionModel" , "DefaultMenuLayout" , "DefaultMetalTheme" , "DefaultMutableTreeNode" , "DefaultPersistenceDelegate" , "DefaultSelectionType" , "DefaultSingleSelectionModel" , "DefaultStyledDocument" , "DefaultTableCellRenderer" , "DefaultTableColumnModel" , "DefaultTableModel" , "DefaultTextUI" , "DefaultTreeCellEditor" , "DefaultTreeCellRenderer" , "DefaultTreeModel" , "DefaultTreeSelectionModel" , "DefinitionKind" , "DefinitionKindHelper" , "Deflater" , "DeflaterOutputStream" , "Delegate" , "DelegationPermission" , "DesignMode" , "DesktopIconUI" , "DesktopManager" , "DesktopPaneUI" , "Destination" , "DestinationType" , "DestroyFailedException" , "Destroyable" , "Dialog" , "DialogType" , "Dictionary" , "DigestException" , "DigestInputStream" , "DigestOutputStream" , "Dimension" , "Dimension2D" , "DimensionUIResource" , "DirContext" , "DirObjectFactory" , "DirStateFactory" , "DirectColorModel" , "DirectoryManager" , "DisplayMode" , "DnDConstants" , "Doc" , "DocAttribute" , "DocAttributeSet" , "DocFlavor" , "DocPrintJob" , "Document" , "DocumentBuilder" , "DocumentBuilderFactory" , "DocumentEvent" , "DocumentFilter" , "DocumentFragment" , "DocumentHandler" , "DocumentListener" , "DocumentName" , "DocumentParser" , "DocumentType" , "DomainCombiner" , "DomainManager" , "DomainManagerOperations" , "Double" , "DoubleBuffer" , "DoubleHolder" , "DoubleSeqHelper" , "DoubleSeqHolder" , "DragGestureEvent" , "DragGestureListener" , "DragGestureRecognizer" , "DragSource" , "DragSourceAdapter" , "DragSourceContext" , "DragSourceDragEvent" , "DragSourceDropEvent" , "DragSourceEvent" , "DragSourceListener" , "DragSourceMotionListener" , "Driver" , "DriverManager" , "DriverPropertyInfo" , "DropTarget" , "DropTargetAdapter" , "DropTargetAutoScroller" , "DropTargetContext" , "DropTargetDragEvent" , "DropTargetDropEvent" , "DropTargetEvent" , "DropTargetListener" , "DuplicateName" , "DuplicateNameHelper" , "DynAny" , "DynAnyFactory" , "DynAnyFactoryHelper" , "DynAnyFactoryOperations" , "DynAnyHelper" , "DynAnyOperations" , "DynAnySeqHelper" , "DynArray" , "DynArrayHelper" , "DynArrayOperations" , "DynEnum" , "DynEnumHelper" , "DynEnumOperations" , "DynFixed" , "DynFixedHelper" , "DynFixedOperations" , "DynSequence" , "DynSequenceHelper" , "DynSequenceOperations" , "DynStruct" , "DynStructHelper" , "DynStructOperations" , "DynUnion" , "DynUnionHelper" , "DynUnionOperations" , "DynValue" , "DynValueBox" , "DynValueBoxOperations" , "DynValueCommon" , "DynValueCommonOperations" , "DynValueHelper" , "DynValueOperations" , "DynamicImplementation" , "DynamicUtilTreeNode" , "ENCODING_CDR_ENCAPS" , "EOFException" , "EditorKit" , "Element" , "ElementChange" , "ElementEdit" , "ElementIterator" , "ElementSpec" , "Ellipse2D" , "EmptyBorder" , "EmptyBorderUIResource" , "EmptySelectionModel" , "EmptyStackException" , "EncodedKeySpec" , "Encoder" , "Encoding" , "EncryptedPrivateKeyInfo" , "Engineering" , "Entity" , "EntityReference" , "EntityResolver" , "Entry" , "EnumControl" , "EnumSyntax" , "Enumeration" , "Environment" , "Error" , "ErrorHandler" , "ErrorListener" , "ErrorManager" , "EtchedBorder" , "EtchedBorderUIResource" , "Event" , "EventContext" , "EventDirContext" , "EventHandler" , "EventListener" , "EventListenerList" , "EventListenerProxy" , "EventObject" , "EventQueue" , "EventSetDescriptor" , "EventType" , "Exception" , "ExceptionInInitializerError" , "ExceptionList" , "ExceptionListener" , "ExemptionMechanism" , "ExemptionMechanismException" , "ExemptionMechanismSpi" , "ExpandVetoException" , "ExportException" , "Expression" , "ExtendedRequest" , "ExtendedResponse" , "Externalizable" , "FREE_MEM" , "FactoryConfigurationError" , "FailedLoginException" , "FeatureDescriptor" , "Fidelity" , "Field" , "FieldBorder" , "FieldNameHelper" , "FieldPosition" , "FieldView" , "File" , "FileCacheImageInputStream" , "FileCacheImageOutputStream" , "FileChannel" , "FileChooserUI" , "FileDescriptor" , "FileDialog" , "FileFilter" , "FileHandler" , "FileIcon16" , "FileImageInputStream" , "FileImageOutputStream" , "FileInputStream" , "FileLock" , "FileLockInterruptionException" , "FileNameMap" , "FileNotFoundException" , "FileOutputStream" , "FilePermission" , "FileReader" , "FileSystemView" , "FileView" , "FileWriter" , "FilenameFilter" , "Filler" , "Filter" , "FilterBypass" , "FilterInputStream" , "FilterOutputStream" , "FilterReader" , "FilterWriter" , "FilteredImageSource" , "Finishings" , "FixedHeightLayoutCache" , "FixedHolder" , "FlatteningPathIterator" , "FlavorException" , "FlavorMap" , "FlavorTable" , "FlipContents" , "Float" , "FloatBuffer" , "FloatControl" , "FloatHolder" , "FloatSeqHelper" , "FloatSeqHolder" , "FlowLayout" , "FlowStrategy" , "FlowView" , "Flush3DBorder" , "FocusAdapter" , "FocusEvent" , "FocusListener" , "FocusManager" , "FocusTraversalPolicy" , "FolderIcon16" , "Font" , "FontAttribute" , "FontConstants" , "FontFamilyAction" , "FontFormatException" , "FontMetrics" , "FontRenderContext" , "FontSizeAction" , "FontUIResource" , "ForegroundAction" , "FormView" , "Format" , "FormatConversionProvider" , "FormatMismatch" , "FormatMismatchHelper" , "Formatter" , "ForwardRequest" , "ForwardRequestHelper" , "Frame" , "GSSContext" , "GSSCredential" , "GSSException" , "GSSManager" , "GSSName" , "GZIPInputStream" , "GZIPOutputStream" , "GapContent" , "GatheringByteChannel" , "GeneralPath" , "GeneralSecurityException" , "GetField" , "GlyphJustificationInfo" , "GlyphMetrics" , "GlyphPainter" , "GlyphVector" , "GlyphView" , "GradientPaint" , "GraphicAttribute" , "Graphics" , "Graphics2D" , "GraphicsConfigTemplate" , "GraphicsConfiguration" , "GraphicsDevice" , "GraphicsEnvironment" , "GrayFilter" , "GregorianCalendar" , "GridBagConstraints" , "GridBagLayout" , "GridLayout" , "Group" , "Guard" , "GuardedObject" , "HTML" , "HTMLDocument" , "HTMLEditorKit" , "HTMLFrameHyperlinkEvent" , "HTMLWriter" , "Handler" , "HandlerBase" , "HandshakeCompletedEvent" , "HandshakeCompletedListener" , "HasControls" , "HashAttributeSet" , "HashDocAttributeSet" , "HashMap" , "HashPrintJobAttributeSet" , "HashPrintRequestAttributeSet" , "HashPrintServiceAttributeSet" , "HashSet" , "Hashtable" , "HeadlessException" , "HierarchyBoundsAdapter" , "HierarchyBoundsListener" , "HierarchyEvent" , "HierarchyListener" , "Highlight" , "HighlightPainter" , "Highlighter" , "HostnameVerifier" , "HttpURLConnection" , "HttpsURLConnection" , "HyperlinkEvent" , "HyperlinkListener" , "ICC_ColorSpace" , "ICC_Profile" , "ICC_ProfileGray" , "ICC_ProfileRGB" , "IDLEntity" , "IDLType" , "IDLTypeHelper" , "IDLTypeOperations" , "ID_ASSIGNMENT_POLICY_ID" , "ID_UNIQUENESS_POLICY_ID" , "IIOByteBuffer" , "IIOException" , "IIOImage" , "IIOInvalidTreeException" , "IIOMetadata" , "IIOMetadataController" , "IIOMetadataFormat" , "IIOMetadataFormatImpl" , "IIOMetadataNode" , "IIOParam" , "IIOParamController" , "IIOReadProgressListener" , "IIOReadUpdateListener" , "IIOReadWarningListener" , "IIORegistry" , "IIOServiceProvider" , "IIOWriteProgressListener" , "IIOWriteWarningListener" , "IMPLICIT_ACTIVATION_POLICY_ID" , "IMP_LIMIT" , "INITIALIZE" , "INPUT_STREAM" , "INTERNAL" , "INTF_REPOS" , "INVALID_TRANSACTION" , "INV_FLAG" , "INV_IDENT" , "INV_OBJREF" , "INV_POLICY" , "IOException" , "IOR" , "IORHelper" , "IORHolder" , "IORInfo" , "IORInfoOperations" , "IORInterceptor" , "IORInterceptorOperations" , "IRObject" , "IRObjectOperations" , "ISO" , "Icon" , "IconUIResource" , "IconView" , "IdAssignmentPolicy" , "IdAssignmentPolicyOperations" , "IdAssignmentPolicyValue" , "IdUniquenessPolicy" , "IdUniquenessPolicyOperations" , "IdUniquenessPolicyValue" , "IdentifierHelper" , "Identity" , "IdentityHashMap" , "IdentityScope" , "IllegalAccessError" , "IllegalAccessException" , "IllegalArgumentException" , "IllegalBlockSizeException" , "IllegalBlockingModeException" , "IllegalCharsetNameException" , "IllegalComponentStateException" , "IllegalMonitorStateException" , "IllegalPathStateException" , "IllegalSelectorException" , "IllegalStateException" , "IllegalThreadStateException" , "Image" , "ImageCapabilities" , "ImageConsumer" , "ImageFilter" , "ImageGraphicAttribute" , "ImageIO" , "ImageIcon" , "ImageInputStream" , "ImageInputStreamImpl" , "ImageInputStreamSpi" , "ImageObserver" , "ImageOutputStream" , "ImageOutputStreamImpl" , "ImageOutputStreamSpi" , "ImageProducer" , "ImageReadParam" , "ImageReader" , "ImageReaderSpi" , "ImageReaderWriterSpi" , "ImageTranscoder" , "ImageTranscoderSpi" , "ImageTypeSpecifier" , "ImageView" , "ImageWriteParam" , "ImageWriter" , "ImageWriterSpi" , "ImagingOpException" , "ImplicitActivationPolicy" , "ImplicitActivationPolicyOperations" , "ImplicitActivationPolicyValue" , "IncompatibleClassChangeError" , "InconsistentTypeCode" , "InconsistentTypeCodeHelper" , "IndexColorModel" , "IndexOutOfBoundsException" , "IndexedPropertyDescriptor" , "IndirectionException" , "Inet4Address" , "Inet6Address" , "InetAddress" , "InetSocketAddress" , "Inflater" , "InflaterInputStream" , "Info" , "InheritableThreadLocal" , "InitialContext" , "InitialContextFactory" , "InitialContextFactoryBuilder" , "InitialDirContext" , "InitialLdapContext" , "InlineView" , "InputContext" , "InputEvent" , "InputMap" , "InputMapUIResource" , "InputMethod" , "InputMethodContext" , "InputMethodDescriptor" , "InputMethodEvent" , "InputMethodHighlight" , "InputMethodListener" , "InputMethodRequests" , "InputSource" , "InputStream" , "InputStreamReader" , "InputSubset" , "InputVerifier" , "InsertBreakAction" , "InsertContentAction" , "InsertHTMLTextAction" , "InsertTabAction" , "Insets" , "InsetsUIResource" , "InstantiationError" , "InstantiationException" , "Instrument" , "InsufficientResourcesException" , "IntBuffer" , "IntHolder" , "Integer" , "IntegerSyntax" , "Interceptor" , "InterceptorOperations" , "InternalError" , "InternalFrameAdapter" , "InternalFrameBorder" , "InternalFrameEvent" , "InternalFrameFocusTraversalPolicy" , "InternalFrameListener" , "InternalFrameUI" , "InternationalFormatter" , "InterruptedException" , "InterruptedIOException" , "InterruptedNamingException" , "InterruptibleChannel" , "IntrospectionException" , "Introspector" , "Invalid" , "InvalidAddress" , "InvalidAddressHelper" , "InvalidAddressHolder" , "InvalidAlgorithmParameterException" , "InvalidAttributeIdentifierException" , "InvalidAttributeValueException" , "InvalidAttributesException" , "InvalidClassException" , "InvalidDnDOperationException" , "InvalidKeyException" , "InvalidKeySpecException" , "InvalidMarkException" , "InvalidMidiDataException" , "InvalidName" , "InvalidNameException" , "InvalidNameHelper" , "InvalidNameHolder" , "InvalidObjectException" , "InvalidParameterException" , "InvalidParameterSpecException" , "InvalidPolicy" , "InvalidPolicyHelper" , "InvalidPreferencesFormatException" , "InvalidSearchControlsException" , "InvalidSearchFilterException" , "InvalidSeq" , "InvalidSlot" , "InvalidSlotHelper" , "InvalidTransactionException" , "InvalidTypeForEncoding" , "InvalidTypeForEncodingHelper" , "InvalidValue" , "InvalidValueHelper" , "InvocationEvent" , "InvocationHandler" , "InvocationTargetException" , "InvokeHandler" , "IstringHelper" , "ItalicAction" , "ItemEvent" , "ItemListener" , "ItemSelectable" , "Iterator" , "IvParameterSpec" , "JApplet" , "JButton" , "JCheckBox" , "JCheckBoxMenuItem" , "JColorChooser" , "JComboBox" , "JComponent" , "JDesktopIcon" , "JDesktopPane" , "JDialog" , "JEditorPane" , "JFileChooser" , "JFormattedTextField" , "JFrame" , "JIS" , "JInternalFrame" , "JLabel" , "JLayeredPane" , "JList" , "JMenu" , "JMenuBar" , "JMenuItem" , "JOptionPane" , "JPEGHuffmanTable" , "JPEGImageReadParam" , "JPEGImageWriteParam" , "JPEGQTable" , "JPanel" , "JPasswordField" , "JPopupMenu" , "JProgressBar" , "JRadioButton" , "JRadioButtonMenuItem" , "JRootPane" , "JScrollBar" , "JScrollPane" , "JSeparator" , "JSlider" , "JSpinner" , "JSplitPane" , "JTabbedPane" , "JTable" , "JTableHeader" , "JTextArea" , "JTextComponent" , "JTextField" , "JTextPane" , "JToggleButton" , "JToolBar" , "JToolTip" , "JTree" , "JViewport" , "JWindow" , "JarEntry" , "JarException" , "JarFile" , "JarInputStream" , "JarOutputStream" , "JarURLConnection" , "JobAttributes" , "JobHoldUntil" , "JobImpressions" , "JobImpressionsCompleted" , "JobImpressionsSupported" , "JobKOctets" , "JobKOctetsProcessed" , "JobKOctetsSupported" , "JobMediaSheets" , "JobMediaSheetsCompleted" , "JobMediaSheetsSupported" , "JobMessageFromOperator" , "JobName" , "JobOriginatingUserName" , "JobPriority" , "JobPrioritySupported" , "JobSheets" , "JobState" , "JobStateReason" , "JobStateReasons" , "KerberosKey" , "KerberosPrincipal" , "KerberosTicket" , "Kernel" , "Key" , "KeyAdapter" , "KeyAgreement" , "KeyAgreementSpi" , "KeyBinding" , "KeyEvent" , "KeyEventDispatcher" , "KeyEventPostProcessor" , "KeyException" , "KeyFactory" , "KeyFactorySpi" , "KeyGenerator" , "KeyGeneratorSpi" , "KeyListener" , "KeyManagementException" , "KeyManager" , "KeyManagerFactory" , "KeyManagerFactorySpi" , "KeyPair" , "KeyPairGenerator" , "KeyPairGeneratorSpi" , "KeySelectionManager" , "KeySpec" , "KeyStore" , "KeyStoreException" , "KeyStoreSpi" , "KeyStroke" , "KeyboardFocusManager" , "Keymap" , "LDAPCertStoreParameters" , "LIFESPAN_POLICY_ID" , "LOCATION_FORWARD" , "Label" , "LabelUI" , "LabelView" , "LanguageCallback" , "LastOwnerException" , "LayerPainter" , "LayeredHighlighter" , "LayoutFocusTraversalPolicy" , "LayoutManager" , "LayoutManager2" , "LayoutQueue" , "LazyInputMap" , "LazyValue" , "LdapContext" , "LdapReferralException" , "Lease" , "Level" , "LexicalHandler" , "LifespanPolicy" , "LifespanPolicyOperations" , "LifespanPolicyValue" , "LimitExceededException" , "Line" , "Line2D" , "LineBorder" , "LineBorderUIResource" , "LineBreakMeasurer" , "LineEvent" , "LineListener" , "LineMetrics" , "LineNumberInputStream" , "LineNumberReader" , "LineUnavailableException" , "LinkController" , "LinkException" , "LinkLoopException" , "LinkRef" , "LinkageError" , "LinkedHashMap" , "LinkedHashSet" , "LinkedList" , "List" , "ListCellRenderer" , "ListDataEvent" , "ListDataListener" , "ListEditor" , "ListIterator" , "ListModel" , "ListPainter" , "ListResourceBundle" , "ListSelectionEvent" , "ListSelectionListener" , "ListSelectionModel" , "ListUI" , "ListView" , "LoaderHandler" , "LocalObject" , "Locale" , "LocateRegistry" , "Locator" , "LocatorImpl" , "LogManager" , "LogRecord" , "LogStream" , "Logger" , "LoggingPermission" , "LoginContext" , "LoginException" , "LoginModule" , "LoginModuleControlFlag" , "Long" , "LongBuffer" , "LongHolder" , "LongLongSeqHelper" , "LongLongSeqHolder" , "LongSeqHelper" , "LongSeqHolder" , "LookAndFeel" , "LookAndFeelInfo" , "LookupOp" , "LookupTable" , "MARSHAL" , "Mac" , "MacSpi" , "MalformedInputException" , "MalformedLinkException" , "MalformedURLException" , "ManagerFactoryParameters" , "Manifest" , "Map" , "MapMode" , "MappedByteBuffer" , "MarginBorder" , "MarshalException" , "MarshalledObject" , "MaskFormatter" , "Matcher" , "Math" , "MatteBorder" , "MatteBorderUIResource" , "Media" , "MediaName" , "MediaPrintableArea" , "MediaSize" , "MediaSizeName" , "MediaTracker" , "MediaTray" , "MediaType" , "Member" , "MemoryCacheImageInputStream" , "MemoryCacheImageOutputStream" , "MemoryHandler" , "MemoryImageSource" , "Menu" , "MenuBar" , "MenuBarBorder" , "MenuBarUI" , "MenuComponent" , "MenuContainer" , "MenuDragMouseEvent" , "MenuDragMouseListener" , "MenuElement" , "MenuEvent" , "MenuItem" , "MenuItemBorder" , "MenuItemUI" , "MenuKeyEvent" , "MenuKeyListener" , "MenuListener" , "MenuSelectionManager" , "MenuShortcut" , "MessageDigest" , "MessageDigestSpi" , "MessageFormat" , "MessageProp" , "MetaEventListener" , "MetaMessage" , "MetalBorders" , "MetalButtonUI" , "MetalCheckBoxIcon" , "MetalCheckBoxUI" , "MetalComboBoxButton" , "MetalComboBoxEditor" , "MetalComboBoxIcon" , "MetalComboBoxUI" , "MetalDesktopIconUI" , "MetalFileChooserUI" , "MetalIconFactory" , "MetalInternalFrameTitlePane" , "MetalInternalFrameUI" , "MetalLabelUI" , "MetalLookAndFeel" , "MetalPopupMenuSeparatorUI" , "MetalProgressBarUI" , "MetalRadioButtonUI" , "MetalRootPaneUI" , "MetalScrollBarUI" , "MetalScrollButton" , "MetalScrollPaneUI" , "MetalSeparatorUI" , "MetalSliderUI" , "MetalSplitPaneUI" , "MetalTabbedPaneUI" , "MetalTextFieldUI" , "MetalTheme" , "MetalToggleButtonUI" , "MetalToolBarUI" , "MetalToolTipUI" , "MetalTreeUI" , "Method" , "MethodDescriptor" , "MidiChannel" , "MidiDevice" , "MidiDeviceProvider" , "MidiEvent" , "MidiFileFormat" , "MidiFileReader" , "MidiFileWriter" , "MidiMessage" , "MidiSystem" , "MidiUnavailableException" , "MimeTypeParseException" , "MinimalHTMLWriter" , "MissingResourceException" , "Mixer" , "MixerProvider" , "ModificationItem" , "Modifier" , "MouseAdapter" , "MouseDragGestureRecognizer" , "MouseEvent" , "MouseInputAdapter" , "MouseInputListener" , "MouseListener" , "MouseMotionAdapter" , "MouseMotionListener" , "MouseWheelEvent" , "MouseWheelListener" , "MultiButtonUI" , "MultiColorChooserUI" , "MultiComboBoxUI" , "MultiDesktopIconUI" , "MultiDesktopPaneUI" , "MultiDoc" , "MultiDocPrintJob" , "MultiDocPrintService" , "MultiFileChooserUI" , "MultiInternalFrameUI" , "MultiLabelUI" , "MultiListUI" , "MultiLookAndFeel" , "MultiMenuBarUI" , "MultiMenuItemUI" , "MultiOptionPaneUI" , "MultiPanelUI" , "MultiPixelPackedSampleModel" , "MultiPopupMenuUI" , "MultiProgressBarUI" , "MultiRootPaneUI" , "MultiScrollBarUI" , "MultiScrollPaneUI" , "MultiSeparatorUI" , "MultiSliderUI" , "MultiSpinnerUI" , "MultiSplitPaneUI" , "MultiTabbedPaneUI" , "MultiTableHeaderUI" , "MultiTableUI" , "MultiTextUI" , "MultiToolBarUI" , "MultiToolTipUI" , "MultiTreeUI" , "MultiViewportUI" , "MulticastSocket" , "MultipleComponentProfileHelper" , "MultipleComponentProfileHolder" , "MultipleDocumentHandling" , "MultipleDocumentHandlingType" , "MultipleMaster" , "MutableAttributeSet" , "MutableComboBoxModel" , "MutableTreeNode" , "NA" , "NO_IMPLEMENT" , "NO_MEMORY" , "NO_PERMISSION" , "NO_RESOURCES" , "NO_RESPONSE" , "NVList" , "Name" , "NameAlreadyBoundException" , "NameCallback" , "NameClassPair" , "NameComponent" , "NameComponentHelper" , "NameComponentHolder" , "NameDynAnyPair" , "NameDynAnyPairHelper" , "NameDynAnyPairSeqHelper" , "NameHelper" , "NameHolder" , "NameNotFoundException" , "NameParser" , "NameValuePair" , "NameValuePairHelper" , "NameValuePairSeqHelper" , "NamedNodeMap" , "NamedValue" , "NamespaceChangeListener" , "NamespaceSupport" , "Naming" , "NamingContext" , "NamingContextExt" , "NamingContextExtHelper" , "NamingContextExtHolder" , "NamingContextExtOperations" , "NamingContextExtPOA" , "NamingContextHelper" , "NamingContextHolder" , "NamingContextOperations" , "NamingContextPOA" , "NamingEnumeration" , "NamingEvent" , "NamingException" , "NamingExceptionEvent" , "NamingListener" , "NamingManager" , "NamingSecurityException" , "NavigationFilter" , "NegativeArraySizeException" , "NetPermission" , "NetworkInterface" , "NoClassDefFoundError" , "NoConnectionPendingException" , "NoContext" , "NoContextHelper" , "NoInitialContextException" , "NoPermissionException" , "NoRouteToHostException" , "NoServant" , "NoServantHelper" , "NoSuchAlgorithmException" , "NoSuchAttributeException" , "NoSuchElementException" , "NoSuchFieldError" , "NoSuchFieldException" , "NoSuchMethodError" , "NoSuchMethodException" , "NoSuchObjectException" , "NoSuchPaddingException" , "NoSuchProviderException" , "Node" , "NodeChangeEvent" , "NodeChangeListener" , "NodeDimensions" , "NodeList" , "NonReadableChannelException" , "NonWritableChannelException" , "NoninvertibleTransformException" , "NotActiveException" , "NotBoundException" , "NotContextException" , "NotEmpty" , "NotEmptyHelper" , "NotEmptyHolder" , "NotFound" , "NotFoundHelper" , "NotFoundHolder" , "NotFoundReason" , "NotFoundReasonHelper" , "NotFoundReasonHolder" , "NotOwnerException" , "NotSerializableException" , "NotYetBoundException" , "NotYetConnectedException" , "Notation" , "NullCipher" , "NullPointerException" , "Number" , "NumberEditor" , "NumberFormat" , "NumberFormatException" , "NumberFormatter" , "NumberOfDocuments" , "NumberOfInterveningJobs" , "NumberUp" , "NumberUpSupported" , "NumericShaper" , "OBJECT_NOT_EXIST" , "OBJ_ADAPTER" , "OMGVMCID" , "ORB" , "ORBInitInfo" , "ORBInitInfoOperations" , "ORBInitializer" , "ORBInitializerOperations" , "ObjID" , "Object" , "ObjectAlreadyActive" , "ObjectAlreadyActiveHelper" , "ObjectChangeListener" , "ObjectFactory" , "ObjectFactoryBuilder" , "ObjectHelper" , "ObjectHolder" , "ObjectIdHelper" , "ObjectImpl" , "ObjectInput" , "ObjectInputStream" , "ObjectInputValidation" , "ObjectNotActive" , "ObjectNotActiveHelper" , "ObjectOutput" , "ObjectOutputStream" , "ObjectStreamClass" , "ObjectStreamConstants" , "ObjectStreamException" , "ObjectStreamField" , "ObjectView" , "Observable" , "Observer" , "OctetSeqHelper" , "OctetSeqHolder" , "Oid" , "OpenType" , "Operation" , "OperationNotSupportedException" , "Option" , "OptionDialogBorder" , "OptionPaneUI" , "OptionalDataException" , "OrientationRequested" , "OrientationRequestedType" , "OriginType" , "Other" , "OutOfMemoryError" , "OutputDeviceAssigned" , "OutputKeys" , "OutputStream" , "OutputStreamWriter" , "OverlappingFileLockException" , "OverlayLayout" , "Owner" , "PBEKey" , "PBEKeySpec" , "PBEParameterSpec" , "PDLOverrideSupported" , "PERSIST_STORE" , "PKCS8EncodedKeySpec" , "PKIXBuilderParameters" , "PKIXCertPathBuilderResult" , "PKIXCertPathChecker" , "PKIXCertPathValidatorResult" , "PKIXParameters" , "POA" , "POAHelper" , "POAManager" , "POAManagerOperations" , "POAOperations" , "PRIVATE_MEMBER" , "PSSParameterSpec" , "PUBLIC_MEMBER" , "Package" , "PackedColorModel" , "PageAttributes" , "PageFormat" , "PageRanges" , "Pageable" , "PagesPerMinute" , "PagesPerMinuteColor" , "Paint" , "PaintContext" , "PaintEvent" , "PaletteBorder" , "PaletteCloseIcon" , "Panel" , "PanelUI" , "Paper" , "ParagraphAttribute" , "ParagraphConstants" , "ParagraphView" , "Parameter" , "ParameterBlock" , "ParameterDescriptor" , "ParameterMetaData" , "ParameterMode" , "ParameterModeHelper" , "ParameterModeHolder" , "ParseException" , "ParsePosition" , "Parser" , "ParserAdapter" , "ParserCallback" , "ParserConfigurationException" , "ParserDelegator" , "ParserFactory" , "PartialResultException" , "PasswordAuthentication" , "PasswordCallback" , "PasswordView" , "PasteAction" , "Patch" , "PathIterator" , "Pattern" , "PatternSyntaxException" , "Permission" , "PermissionCollection" , "Permissions" , "PersistenceDelegate" , "PhantomReference" , "Pipe" , "PipedInputStream" , "PipedOutputStream" , "PipedReader" , "PipedWriter" , "PixelGrabber" , "PixelInterleavedSampleModel" , "PlainDocument" , "PlainView" , "Point" , "Point2D" , "Policy" , "PolicyError" , "PolicyErrorCodeHelper" , "PolicyErrorHelper" , "PolicyErrorHolder" , "PolicyFactory" , "PolicyFactoryOperations" , "PolicyHelper" , "PolicyHolder" , "PolicyListHelper" , "PolicyListHolder" , "PolicyNode" , "PolicyOperations" , "PolicyQualifierInfo" , "PolicyTypeHelper" , "Polygon" , "PooledConnection" , "Popup" , "PopupFactory" , "PopupMenu" , "PopupMenuBorder" , "PopupMenuEvent" , "PopupMenuListener" , "PopupMenuUI" , "Port" , "PortUnreachableException" , "PortableRemoteObject" , "PortableRemoteObjectDelegate" , "Position" , "PreferenceChangeEvent" , "PreferenceChangeListener" , "Preferences" , "PreferencesFactory" , "PreparedStatement" , "PresentationDirection" , "Principal" , "PrincipalHolder" , "PrintEvent" , "PrintException" , "PrintGraphics" , "PrintJob" , "PrintJobAdapter" , "PrintJobAttribute" , "PrintJobAttributeEvent" , "PrintJobAttributeListener" , "PrintJobAttributeSet" , "PrintJobEvent" , "PrintJobListener" , "PrintQuality" , "PrintQualityType" , "PrintRequestAttribute" , "PrintRequestAttributeSet" , "PrintService" , "PrintServiceAttribute" , "PrintServiceAttributeEvent" , "PrintServiceAttributeListener" , "PrintServiceAttributeSet" , "PrintServiceLookup" , "PrintStream" , "PrintWriter" , "Printable" , "PrinterAbortException" , "PrinterException" , "PrinterGraphics" , "PrinterIOException" , "PrinterInfo" , "PrinterIsAcceptingJobs" , "PrinterJob" , "PrinterLocation" , "PrinterMakeAndModel" , "PrinterMessageFromOperator" , "PrinterMoreInfo" , "PrinterMoreInfoManufacturer" , "PrinterName" , "PrinterResolution" , "PrinterState" , "PrinterStateReason" , "PrinterStateReasons" , "PrinterURI" , "PrivateCredentialPermission" , "PrivateKey" , "PrivilegedAction" , "PrivilegedActionException" , "PrivilegedExceptionAction" , "Process" , "ProcessingInstruction" , "ProfileDataException" , "ProfileIdHelper" , "ProgressBarUI" , "ProgressMonitor" , "ProgressMonitorInputStream" , "Properties" , "PropertyChangeEvent" , "PropertyChangeListener" , "PropertyChangeListenerProxy" , "PropertyChangeSupport" , "PropertyDescriptor" , "PropertyEditor" , "PropertyEditorManager" , "PropertyEditorSupport" , "PropertyPermission" , "PropertyResourceBundle" , "PropertyVetoException" , "ProtectionDomain" , "ProtocolException" , "Provider" , "ProviderException" , "Proxy" , "ProxyLazyValue" , "PublicKey" , "PushbackInputStream" , "PushbackReader" , "PutField" , "QuadCurve2D" , "QueuedJobCount" , "RC2ParameterSpec" , "RC5ParameterSpec" , "READER" , "REQUEST_PROCESSING_POLICY_ID" , "RGBImageFilter" , "RMIClassLoader" , "RMIClassLoaderSpi" , "RMIClientSocketFactory" , "RMIFailureHandler" , "RMISecurityException" , "RMISecurityManager" , "RMIServerSocketFactory" , "RMISocketFactory" , "RSAKey" , "RSAKeyGenParameterSpec" , "RSAMultiPrimePrivateCrtKey" , "RSAMultiPrimePrivateCrtKeySpec" , "RSAOtherPrimeInfo" , "RSAPrivateCrtKey" , "RSAPrivateCrtKeySpec" , "RSAPrivateKey" , "RSAPrivateKeySpec" , "RSAPublicKey" , "RSAPublicKeySpec" , "RTFEditorKit" , "RadioButtonBorder" , "Random" , "RandomAccess" , "RandomAccessFile" , "Raster" , "RasterFormatException" , "RasterOp" , "ReadOnlyBufferException" , "ReadableByteChannel" , "Reader" , "Receiver" , "Rectangle" , "Rectangle2D" , "RectangularShape" , "Ref" , "RefAddr" , "Reference" , "ReferenceQueue" , "ReferenceUriSchemesSupported" , "Referenceable" , "ReferralException" , "ReflectPermission" , "RefreshFailedException" , "Refreshable" , "RegisterableService" , "Registry" , "RegistryHandler" , "RemarshalException" , "Remote" , "RemoteCall" , "RemoteException" , "RemoteObject" , "RemoteRef" , "RemoteServer" , "RemoteStub" , "RenderContext" , "RenderableImage" , "RenderableImageOp" , "RenderableImageProducer" , "RenderedImage" , "RenderedImageFactory" , "Renderer" , "RenderingHints" , "RepaintManager" , "ReplicateScaleFilter" , "RepositoryIdHelper" , "Request" , "RequestInfo" , "RequestInfoOperations" , "RequestProcessingPolicy" , "RequestProcessingPolicyOperations" , "RequestProcessingPolicyValue" , "RequestingUserName" , "RescaleOp" , "ResolutionSyntax" , "ResolveResult" , "Resolver" , "ResourceBundle" , "ResponseHandler" , "Result" , "ResultSet" , "ResultSetMetaData" , "ReverbType" , "Robot" , "RolloverButtonBorder" , "RootPaneContainer" , "RootPaneUI" , "RoundRectangle2D" , "RowMapper" , "RowSet" , "RowSetEvent" , "RowSetInternal" , "RowSetListener" , "RowSetMetaData" , "RowSetReader" , "RowSetWriter" , "RuleBasedCollator" , "RunTime" , "RunTimeOperations" , "Runnable" , "Runtime" , "RuntimeException" , "RuntimePermission" , "SAXException" , "SAXNotRecognizedException" , "SAXNotSupportedException" , "SAXParseException" , "SAXParser" , "SAXParserFactory" , "SAXResult" , "SAXSource" , "SAXTransformerFactory" , "SERVANT_RETENTION_POLICY_ID" , "SERVICE_FORMATTED" , "SQLData" , "SQLException" , "SQLInput" , "SQLOutput" , "SQLPermission" , "SQLWarning" , "SSLContext" , "SSLContextSpi" , "SSLException" , "SSLHandshakeException" , "SSLKeyException" , "SSLPeerUnverifiedException" , "SSLPermission" , "SSLProtocolException" , "SSLServerSocket" , "SSLServerSocketFactory" , "SSLSession" , "SSLSessionBindingEvent" , "SSLSessionBindingListener" , "SSLSessionContext" , "SSLSocket" , "SSLSocketFactory" , "STRING" , "SUCCESSFUL" , "SYNC_WITH_TRANSPORT" , "SYSTEM_EXCEPTION" , "SampleModel" , "Savepoint" , "ScatteringByteChannel" , "SchemaViolationException" , "ScrollBarUI" , "ScrollPane" , "ScrollPaneAdjustable" , "ScrollPaneBorder" , "ScrollPaneConstants" , "ScrollPaneLayout" , "ScrollPaneUI" , "Scrollable" , "Scrollbar" , "SealedObject" , "SearchControls" , "SearchResult" , "SecretKey" , "SecretKeyFactory" , "SecretKeyFactorySpi" , "SecretKeySpec" , "SecureClassLoader" , "SecureRandom" , "SecureRandomSpi" , "Security" , "SecurityException" , "SecurityManager" , "SecurityPermission" , "Segment" , "SelectableChannel" , "SelectionKey" , "Selector" , "SelectorProvider" , "Separator" , "SeparatorUI" , "Sequence" , "SequenceInputStream" , "Sequencer" , "Serializable" , "SerializablePermission" , "Servant" , "ServantActivator" , "ServantActivatorHelper" , "ServantActivatorOperations" , "ServantActivatorPOA" , "ServantAlreadyActive" , "ServantAlreadyActiveHelper" , "ServantLocator" , "ServantLocatorHelper" , "ServantLocatorOperations" , "ServantLocatorPOA" , "ServantManager" , "ServantManagerOperations" , "ServantNotActive" , "ServantNotActiveHelper" , "ServantObject" , "ServantRetentionPolicy" , "ServantRetentionPolicyOperations" , "ServantRetentionPolicyValue" , "ServerCloneException" , "ServerError" , "ServerException" , "ServerNotActiveException" , "ServerRef" , "ServerRequest" , "ServerRequestInfo" , "ServerRequestInfoOperations" , "ServerRequestInterceptor" , "ServerRequestInterceptorOperations" , "ServerRuntimeException" , "ServerSocket" , "ServerSocketChannel" , "ServerSocketFactory" , "ServiceContext" , "ServiceContextHelper" , "ServiceContextHolder" , "ServiceContextListHelper" , "ServiceContextListHolder" , "ServiceDetail" , "ServiceDetailHelper" , "ServiceIdHelper" , "ServiceInformation" , "ServiceInformationHelper" , "ServiceInformationHolder" , "ServicePermission" , "ServiceRegistry" , "ServiceUI" , "ServiceUIFactory" , "ServiceUnavailableException" , "Set" , "SetOfIntegerSyntax" , "SetOverrideType" , "SetOverrideTypeHelper" , "Severity" , "Shape" , "ShapeGraphicAttribute" , "SheetCollate" , "Short" , "ShortBuffer" , "ShortBufferException" , "ShortHolder" , "ShortLookupTable" , "ShortMessage" , "ShortSeqHelper" , "ShortSeqHolder" , "Sides" , "SidesType" , "Signature" , "SignatureException" , "SignatureSpi" , "SignedObject" , "Signer" , "SimpleAttributeSet" , "SimpleBeanInfo" , "SimpleDateFormat" , "SimpleDoc" , "SimpleFormatter" , "SimpleTimeZone" , "SinglePixelPackedSampleModel" , "SingleSelectionModel" , "SinkChannel" , "Size2DSyntax" , "SizeLimitExceededException" , "SizeRequirements" , "SizeSequence" , "Skeleton" , "SkeletonMismatchException" , "SkeletonNotFoundException" , "SliderUI" , "Socket" , "SocketAddress" , "SocketChannel" , "SocketException" , "SocketFactory" , "SocketHandler" , "SocketImpl" , "SocketImplFactory" , "SocketOptions" , "SocketPermission" , "SocketSecurityException" , "SocketTimeoutException" , "SoftBevelBorder" , "SoftReference" , "SortedMap" , "SortedSet" , "SortingFocusTraversalPolicy" , "Soundbank" , "SoundbankReader" , "SoundbankResource" , "Source" , "SourceChannel" , "SourceDataLine" , "SourceLocator" , "SpinnerDateModel" , "SpinnerListModel" , "SpinnerModel" , "SpinnerNumberModel" , "SpinnerUI" , "SplitPaneBorder" , "SplitPaneUI" , "Spring" , "SpringLayout" , "Stack" , "StackOverflowError" , "StackTraceElement" , "StartTlsRequest" , "StartTlsResponse" , "State" , "StateEdit" , "StateEditable" , "StateFactory" , "Statement" , "StreamCorruptedException" , "StreamHandler" , "StreamPrintService" , "StreamPrintServiceFactory" , "StreamResult" , "StreamSource" , "StreamTokenizer" , "Streamable" , "StreamableValue" , "StrictMath" , "String" , "StringBuffer" , "StringBufferInputStream" , "StringCharacterIterator" , "StringContent" , "StringHolder" , "StringIndexOutOfBoundsException" , "StringNameHelper" , "StringReader" , "StringRefAddr" , "StringSelection" , "StringSeqHelper" , "StringSeqHolder" , "StringTokenizer" , "StringValueHelper" , "StringWriter" , "Stroke" , "Struct" , "StructMember" , "StructMemberHelper" , "Stub" , "StubDelegate" , "StubNotFoundException" , "Style" , "StyleConstants" , "StyleContext" , "StyleSheet" , "StyledDocument" , "StyledEditorKit" , "StyledTextAction" , "Subject" , "SubjectDomainCombiner" , "Subset" , "SupportedValuesAttribute" , "SwingConstants" , "SwingPropertyChangeSupport" , "SwingUtilities" , "SyncFailedException" , "SyncMode" , "SyncScopeHelper" , "Synthesizer" , "SysexMessage" , "System" , "SystemColor" , "SystemException" , "SystemFlavorMap" , "TAG_ALTERNATE_IIOP_ADDRESS" , "TAG_CODE_SETS" , "TAG_INTERNET_IOP" , "TAG_JAVA_CODEBASE" , "TAG_MULTIPLE_COMPONENTS" , "TAG_ORB_TYPE" , "TAG_POLICIES" , "TCKind" , "THREAD_POLICY_ID" , "TRANSACTION_REQUIRED" , "TRANSACTION_ROLLEDBACK" , "TRANSIENT" , "TRANSPORT_RETRY" , "TabExpander" , "TabSet" , "TabStop" , "TabableView" , "TabbedPaneUI" , "TableCellEditor" , "TableCellRenderer" , "TableColumn" , "TableColumnModel" , "TableColumnModelEvent" , "TableColumnModelListener" , "TableHeaderBorder" , "TableHeaderUI" , "TableModel" , "TableModelEvent" , "TableModelListener" , "TableUI" , "TableView" , "Tag" , "TagElement" , "TaggedComponent" , "TaggedComponentHelper" , "TaggedComponentHolder" , "TaggedProfile" , "TaggedProfileHelper" , "TaggedProfileHolder" , "TargetDataLine" , "Templates" , "TemplatesHandler" , "Text" , "TextAction" , "TextArea" , "TextAttribute" , "TextComponent" , "TextEvent" , "TextField" , "TextFieldBorder" , "TextHitInfo" , "TextInputCallback" , "TextLayout" , "TextListener" , "TextMeasurer" , "TextOutputCallback" , "TextSyntax" , "TextUI" , "TexturePaint" , "Thread" , "ThreadDeath" , "ThreadGroup" , "ThreadLocal" , "ThreadPolicy" , "ThreadPolicyOperations" , "ThreadPolicyValue" , "Throwable" , "Tie" , "TileObserver" , "Time" , "TimeLimitExceededException" , "TimeZone" , "Timer" , "TimerTask" , "Timestamp" , "TitledBorder" , "TitledBorderUIResource" , "ToggleButtonBorder" , "ToggleButtonModel" , "TooManyListenersException" , "ToolBarBorder" , "ToolBarUI" , "ToolTipManager" , "ToolTipUI" , "Toolkit" , "Track" , "TransactionRequiredException" , "TransactionRolledbackException" , "TransactionService" , "TransferHandler" , "Transferable" , "TransformAttribute" , "Transformer" , "TransformerConfigurationException" , "TransformerException" , "TransformerFactory" , "TransformerFactoryConfigurationError" , "TransformerHandler" , "Transmitter" , "Transparency" , "TreeCellEditor" , "TreeCellRenderer" , "TreeControlIcon" , "TreeExpansionEvent" , "TreeExpansionListener" , "TreeFolderIcon" , "TreeLeafIcon" , "TreeMap" , "TreeModel" , "TreeModelEvent" , "TreeModelListener" , "TreeNode" , "TreePath" , "TreeSelectionEvent" , "TreeSelectionListener" , "TreeSelectionModel" , "TreeSet" , "TreeUI" , "TreeWillExpandListener" , "TrustAnchor" , "TrustManager" , "TrustManagerFactory" , "TrustManagerFactorySpi" , "Type" , "TypeCode" , "TypeCodeHolder" , "TypeMismatch" , "TypeMismatchHelper" , "Types" , "UID" , "UIDefaults" , "UIManager" , "UIResource" , "ULongLongSeqHelper" , "ULongLongSeqHolder" , "ULongSeqHelper" , "ULongSeqHolder" , "UNKNOWN" , "UNSUPPORTED_POLICY" , "UNSUPPORTED_POLICY_VALUE" , "URI" , "URIException" , "URIResolver" , "URISyntax" , "URISyntaxException" , "URL" , "URLClassLoader" , "URLConnection" , "URLDecoder" , "URLEncoder" , "URLStreamHandler" , "URLStreamHandlerFactory" , "URLStringHelper" , "USER_EXCEPTION" , "UShortSeqHelper" , "UShortSeqHolder" , "UTFDataFormatException" , "UndeclaredThrowableException" , "UnderlineAction" , "UndoManager" , "UndoableEdit" , "UndoableEditEvent" , "UndoableEditListener" , "UndoableEditSupport" , "UnexpectedException" , "UnicastRemoteObject" , "UnicodeBlock" , "UnionMember" , "UnionMemberHelper" , "UnknownEncoding" , "UnknownEncodingHelper" , "UnknownError" , "UnknownException" , "UnknownGroupException" , "UnknownHostException" , "UnknownObjectException" , "UnknownServiceException" , "UnknownTag" , "UnknownUserException" , "UnknownUserExceptionHelper" , "UnknownUserExceptionHolder" , "UnmappableCharacterException" , "UnmarshalException" , "UnmodifiableSetException" , "UnrecoverableKeyException" , "Unreferenced" , "UnresolvedAddressException" , "UnresolvedPermission" , "UnsatisfiedLinkError" , "UnsolicitedNotification" , "UnsolicitedNotificationEvent" , "UnsolicitedNotificationListener" , "UnsupportedAddressTypeException" , "UnsupportedAudioFileException" , "UnsupportedCallbackException" , "UnsupportedCharsetException" , "UnsupportedClassVersionError" , "UnsupportedEncodingException" , "UnsupportedFlavorException" , "UnsupportedLookAndFeelException" , "UnsupportedOperationException" , "UserException" , "Util" , "UtilDelegate" , "Utilities" , "VMID" , "VM_ABSTRACT" , "VM_CUSTOM" , "VM_NONE" , "VM_TRUNCATABLE" , "ValueBase" , "ValueBaseHelper" , "ValueBaseHolder" , "ValueFactory" , "ValueHandler" , "ValueMember" , "ValueMemberHelper" , "VariableHeightLayoutCache" , "Vector" , "VerifyError" , "VersionSpecHelper" , "VetoableChangeListener" , "VetoableChangeListenerProxy" , "VetoableChangeSupport" , "View" , "ViewFactory" , "ViewportLayout" , "ViewportUI" , "VirtualMachineError" , "Visibility" , "VisibilityHelper" , "VoiceStatus" , "Void" , "VolatileImage" , "WCharSeqHelper" , "WCharSeqHolder" , "WStringSeqHelper" , "WStringSeqHolder" , "WStringValueHelper" , "WeakHashMap" , "WeakReference" , "Window" , "WindowAdapter" , "WindowConstants" , "WindowEvent" , "WindowFocusListener" , "WindowListener" , "WindowStateListener" , "WrappedPlainView" , "WritableByteChannel" , "WritableRaster" , "WritableRenderedImage" , "WriteAbortedException" , "Writer" , "WrongAdapter" , "WrongAdapterHelper" , "WrongPolicy" , "WrongPolicyHelper" , "WrongTransaction" , "WrongTransactionHelper" , "WrongTransactionHolder" , "X500Principal" , "X500PrivateCredential" , "X509CRL" , "X509CRLEntry" , "X509CRLSelector" , "X509CertSelector" , "X509Certificate" , "X509EncodedKeySpec" , "X509Extension" , "X509KeyManager" , "X509TrustManager" , "XAConnection" , "XADataSource" , "XAException" , "XAResource" , "XMLDecoder" , "XMLEncoder" , "XMLFilter" , "XMLFilterImpl" , "XMLFormatter" , "XMLReader" , "XMLReaderAdapter" , "XMLReaderFactory" , "Xid" , "ZipEntry" , "ZipException" , "ZipFile" , "ZipInputStream" , "ZipOutputStream" , "ZoneView" , "_BindingIteratorImplBase" , "_BindingIteratorStub" , "_DynAnyFactoryStub" , "_DynAnyStub" , "_DynArrayStub" , "_DynEnumStub" , "_DynFixedStub" , "_DynSequenceStub" , "_DynStructStub" , "_DynUnionStub" , "_DynValueStub" , "_IDLTypeStub" , "_NamingContextExtStub" , "_NamingContextImplBase" , "_NamingContextStub" , "_PolicyStub" , "_Remote_Stub" , "_ServantActivatorStub" , "_ServantLocatorStub" ]) , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Float , rAttribute = FloatTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [ Rule { rMatcher = AnyChar "fF" , rAttribute = FloatTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCOct , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCHex , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [ Rule { rMatcher = StringDetect "ULL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LUL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LLU" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "UL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LU" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "LL" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "U" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "L" , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCChar , rAttribute = CharTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "//\\s*BEGIN.*$" , reCompiled = Just (compileRegex False "//\\s*BEGIN.*$") , reCaseSensitive = False } , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "//\\s*END.*$" , reCompiled = Just (compileRegex False "//\\s*END.*$") , reCaseSensitive = False } , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Java String" ) ] } , Rule { rMatcher = DetectChar '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '}' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = AnyChar "!%&()+,-<=>?[]^{|}~" , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '/' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Java Single-Line Comment" ) ] } , Rule { rMatcher = Detect2Chars '/' '*' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Java Multi-Line Comment" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Single Quoted Custom Tag Value" , Context { cName = "Jsp Single Quoted Custom Tag Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = DetectChar '\'' , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } ] , cAttribute = DataTypeTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Single Quoted Param Value" , Context { cName = "Jsp Single Quoted Param Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = DetectChar '\'' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } , Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Standard Directive" , Context { cName = "Jsp Standard Directive" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = Detect2Chars '%' '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*=\\s*" , reCompiled = Just (compileRegex False "\\s*=\\s*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Standard Directive Value" ) ] } , Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<\\s*\\/?\\s*\\$?\\w*:\\$?\\w*" , reCompiled = Just (compileRegex False "<\\s*\\/?\\s*\\$?\\w*:\\$?\\w*") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Custom Tag" ) ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Standard Directive Value" , Context { cName = "Jsp Standard Directive Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Double Quoted Param Value" ) ] } , Rule { rMatcher = DetectChar '\'' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Single Quoted Param Value" ) ] } , Rule { rMatcher = Detect2Chars '%' '>' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Xml Directive" , Context { cName = "Jsp Xml Directive" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\s*\\/?\\s*>" , reCompiled = Just (compileRegex False "\\s*\\/?\\s*>") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*=\\s*" , reCompiled = Just (compileRegex False "\\s*=\\s*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Xml Directive Value" ) ] } , Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Jsp Xml Directive Value" , Context { cName = "Jsp Xml Directive Value" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = Detect2Chars '$' '{' , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Expression" ) ] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Double Quoted Param Value" ) ] } , Rule { rMatcher = DetectChar '\'' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Single Quoted Param Value" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\s*\\/?\\s*>" , reCompiled = Just (compileRegex False "\\s*\\/?\\s*>") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Normal" , Context { cName = "Normal" , cSyntax = "JSP" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "<%@\\s*[a-zA-Z0-9_\\.]*" , reCompiled = Just (compileRegex False "<%@\\s*[a-zA-Z0-9_\\.]*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Standard Directive" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<\\s*jsp:(declaration|expression|scriptlet)\\s*>" , reCompiled = Just (compileRegex False "<\\s*jsp:(declaration|expression|scriptlet)\\s*>") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<\\s*\\/?s*jsp:[a-zA-Z0-9_\\.]*" , reCompiled = Just (compileRegex False "<\\s*\\/?s*jsp:[a-zA-Z0-9_\\.]*") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Xml Directive" ) ] } , Rule { rMatcher = StringDetect "<%--" , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Comment" ) ] } , Rule { rMatcher = RegExpr RE { reString = "<%(!|=)?" , reCompiled = Just (compileRegex False "<%(!|=)?") , reCaseSensitive = False } , rAttribute = NormalTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "JSP" , "Jsp Scriptlet" ) ] } , Rule { rMatcher = StringDetect "