Updated runtime files.
diff --git a/runtime/syntax/abap.vim b/runtime/syntax/abap.vim
index 8f7306d..fd4b480 100644
--- a/runtime/syntax/abap.vim
+++ b/runtime/syntax/abap.vim
@@ -1,8 +1,8 @@
 " Vim ABAP syntax file
 "    Language: SAP - ABAP/R4
-"    Revision: 2.0
+"    Revision: 2.1
 "  Maintainer: Marius Piedallu van Wyk <lailoken@gmail.com>
-" Last Change: 2012 Oct 12
+" Last Change: 2012 Oct 23
 "     Comment: Thanks to EPI-USE Labs for all your assistance. :)
 
 " For version  < 6.0: Clear all syntax items
@@ -16,7 +16,7 @@
 " Always ignore case
 syn case ignore
 
-" Symbol Operators
+" Symbol Operators (space delimited)
 syn match   abapSymbolOperator  "\W+\W"
 syn match   abapSymbolOperator  "\W-\W"
 syn match   abapSymbolOperator  "\W/\W"
@@ -49,99 +49,105 @@
   set iskeyword=48-57,_,A-Z,a-z,/
 endif
 
-syn match   abapNamespace        "/\w\+/"
+syn match   abapNamespace        "\</\w\+/"
 
 " multi-word statements
-syn match   abapComplexStatement "\(WITH\W\+\(HEADER\W\+LINE\|FRAME\|KEY\)\|WITH\)"
-syn match   abapComplexStatement "NO\W\+STANDARD\W\+PAGE\W\+HEADING"
-syn match   abapComplexStatement "\(EXIT\W\+FROM\W\+STEP\W\+LOOP\|EXIT\)"
-syn match   abapComplexStatement "\(BEGIN\W\+OF\W\+\(BLOCK\|LINE\)\|BEGIN\W\+OF\)"
-syn match   abapComplexStatement "\(END\W\+OF\W\+\(BLOCK\|LINE\)\|END\W\+OF\)"
-syn match   abapComplexStatement "NO\W\+INTERVALS"
-syn match   abapComplexStatement "RESPECTING\W\+BLANKS"
-syn match   abapComplexStatement "SEPARATED\W\+BY"
-syn match   abapComplexStatement "\(USING\W\+\(EDIT\W\+MASK\)\|USING\)"
-syn match   abapComplexStatement "\(WHERE\W\+\(LINE\)\)"
-syn match   abapComplexStatement "RADIOBUTTON\W\+GROUP"
-syn match   abapComplexStatement "REF\W\+TO"
-syn match   abapComplexStatement "\(PUBLIC\|PRIVATE\|PROTECTED\)\(\W\+SECTION\)\?"
-syn match   abapComplexStatement "DELETING\W\+\(TRAILING\|LEADING\)"
-syn match   abapComplexStatement "\(ALL\W\+OCCURRENCES\)\|\(\(FIRST\|LAST\)\W\+OCCURRENCE\)"
-syn match   abapComplexStatement "INHERITING\W\+FROM"
+syn match   abapComplexStatement "\<\(WITH\W\+\(HEADER\W\+LINE\|FRAME\|KEY\)\|WITH\)\>"
+syn match   abapComplexStatement "\<NO\W\+STANDARD\W\+PAGE\W\+HEADING\>"
+syn match   abapComplexStatement "\<\(EXIT\W\+FROM\W\+STEP\W\+LOOP\|EXIT\)\>"
+syn match   abapComplexStatement "\<\(BEGIN\W\+OF\W\+\(BLOCK\|LINE\)\|BEGIN\W\+OF\)\>"
+syn match   abapComplexStatement "\<\(END\W\+OF\W\+\(BLOCK\|LINE\)\|END\W\+OF\)\>"
+syn match   abapComplexStatement "\<NO\W\+INTERVALS\>"
+syn match   abapComplexStatement "\<RESPECTING\W\+BLANKS\>"
+syn match   abapComplexStatement "\<SEPARATED\W\+BY\>"
+syn match   abapComplexStatement "\<USING\(\W\+EDIT\W\+MASK\)\?\>"
+syn match   abapComplexStatement "\<WHERE\(\W\+LINE\)\?\>"
+syn match   abapComplexStatement "\<RADIOBUTTON\W\+GROUP\>"
+syn match   abapComplexStatement "\<REF\W\+TO\>"
+syn match   abapComplexStatement "\<\(PUBLIC\|PRIVATE\|PROTECTED\)\(\W\+SECTION\)\?\>"
+syn match   abapComplexStatement "\<DELETING\W\+\(TRAILING\|LEADING\)\>"
+syn match   abapComplexStatement "\<\(ALL\W\+OCCURRENCES\)\|\(\(FIRST\|LAST\)\W\+OCCURRENCE\)\>"
+syn match   abapComplexStatement "\<INHERITING\W\+FROM\>"
+syn match   abapComplexStatement "\<\(UP\W\+\)\?TO\>"
 
 " hyphenated-word statements
-syn match   abapComplexStatement "LINE-COUNT"
-syn match   abapComplexStatement "ADD-CORRESPONDING"
-syn match   abapComplexStatement "AUTHORITY-CHECK"
-syn match   abapComplexStatement "BREAK-POINT"
-syn match   abapComplexStatement "CLASS-DATA"
-syn match   abapComplexStatement "CLASS-METHODS"
-syn match   abapComplexStatement "CLASS-METHOD"
-syn match   abapComplexStatement "DIVIDE-CORRESPONDING"
-syn match   abapComplexStatement "EDITOR-CALL"
-syn match   abapComplexStatement "END-OF-DEFINITION"
-syn match   abapComplexStatement "END-OF-PAGE"
-syn match   abapComplexStatement "END-OF-SELECTION"
-syn match   abapComplexStatement "FIELD-GROUPS"
-syn match   abapComplexStatement "FIELD-SYMBOLS"
-syn match   abapComplexStatement "FUNCTION-POOL"
-syn match   abapComplexStatement "MOVE-CORRESPONDING"
-syn match   abapComplexStatement "MULTIPLY-CORRESPONDING"
-syn match   abapComplexStatement "NEW-LINE"
-syn match   abapComplexStatement "NEW-PAGE"
-syn match   abapComplexStatement "NEW-SECTION"
-syn match   abapComplexStatement "PRINT-CONTROL"
-syn match   abapComplexStatement "RP-PROVIDE-FROM-LAST"
-syn match   abapComplexStatement "SELECT-OPTIONS"
-syn match   abapComplexStatement "SELECTION-SCREEN"
-syn match   abapComplexStatement "START-OF-SELECTION"
-syn match   abapComplexStatement "SUBTRACT-CORRESPONDING"
-syn match   abapComplexStatement "SYNTAX-CHECK"
-syn match   abapComplexStatement "SYNTAX-TRACE"
-syn match   abapComplexStatement "TOP-OF-PAGE"
-syn match   abapComplexStatement "TYPE-POOL"
-syn match   abapComplexStatement "TYPE-POOLS"
-syn match   abapComplexStatement "LINE-SIZE"
-syn match   abapComplexStatement "LINE-COUNT"
-syn match   abapComplexStatement "MESSAGE-ID"
-syn match   abapComplexStatement "DISPLAY-MODE"
-syn match   abapComplexStatement "READ\(-ONLY\)\?"
+syn match   abapComplexStatement "\<LINE-COUNT\>"
+syn match   abapComplexStatement "\<ADD-CORRESPONDING\>"
+syn match   abapComplexStatement "\<AUTHORITY-CHECK\>"
+syn match   abapComplexStatement "\<BREAK-POINT\>"
+syn match   abapComplexStatement "\<CLASS-DATA\>"
+syn match   abapComplexStatement "\<CLASS-METHODS\>"
+syn match   abapComplexStatement "\<CLASS-METHOD\>"
+syn match   abapComplexStatement "\<DIVIDE-CORRESPONDING\>"
+syn match   abapComplexStatement "\<EDITOR-CALL\>"
+syn match   abapComplexStatement "\<END-OF-DEFINITION\>"
+syn match   abapComplexStatement "\<END-OF-PAGE\>"
+syn match   abapComplexStatement "\<END-OF-SELECTION\>"
+syn match   abapComplexStatement "\<FIELD-GROUPS\>"
+syn match   abapComplexStatement "\<FIELD-SYMBOLS\>"
+syn match   abapComplexStatement "\<FUNCTION-POOL\>"
+syn match   abapComplexStatement "\<IS\W\+\(NOT\W\+\)\?\(ASSIGNED\|BOUND\|INITIAL\|SUPPLIED\)\>"
+syn match   abapComplexStatement "\<MOVE-CORRESPONDING\>"
+syn match   abapComplexStatement "\<MULTIPLY-CORRESPONDING\>"
+syn match   abapComplexStatement "\<NEW-LINE\>"
+syn match   abapComplexStatement "\<NEW-PAGE\>"
+syn match   abapComplexStatement "\<NEW-SECTION\>"
+syn match   abapComplexStatement "\<PRINT-CONTROL\>"
+syn match   abapComplexStatement "\<RP-PROVIDE-FROM-LAST\>"
+syn match   abapComplexStatement "\<SELECT-OPTIONS\>"
+syn match   abapComplexStatement "\<SELECTION-SCREEN\>"
+syn match   abapComplexStatement "\<START-OF-SELECTION\>"
+syn match   abapComplexStatement "\<SUBTRACT-CORRESPONDING\>"
+syn match   abapComplexStatement "\<SYNTAX-CHECK\>"
+syn match   abapComplexStatement "\<SYNTAX-TRACE\>"
+syn match   abapComplexStatement "\<TOP-OF-PAGE\>"
+syn match   abapComplexStatement "\<TYPE-POOL\>"
+syn match   abapComplexStatement "\<TYPE-POOLS\>"
+syn match   abapComplexStatement "\<LINE-SIZE\>"
+syn match   abapComplexStatement "\<LINE-COUNT\>"
+syn match   abapComplexStatement "\<MESSAGE-ID\>"
+syn match   abapComplexStatement "\<DISPLAY-MODE\>"
+syn match   abapComplexStatement "\<READ\(-ONLY\)\?\>"
 
 " ABAP statements
 syn keyword abapStatement ADD ALIAS ALIASES ASSERT ASSIGN ASSIGNING AT
-syn keyword abapStatement BACK BOUND
+syn keyword abapStatement BACK
 syn keyword abapStatement CALL CASE CATCH CHECK CLASS CLEAR CLOSE CNT COLLECT COMMIT COMMUNICATION COMPUTE CONCATENATE CONDENSE CONSTANTS CONTINUE CONTROLS CONVERT CREATE CURRENCY
 syn keyword abapStatement DATA DEFINE DEFINITION DEFERRED DELETE DESCRIBE DETAIL DIVIDE DO
 syn keyword abapStatement ELSE ELSEIF ENDAT ENDCASE ENDCLASS ENDDO ENDEXEC ENDFORM ENDFUNCTION ENDIF ENDIFEND ENDINTERFACE ENDLOOP ENDMETHOD ENDMODULE ENDON ENDPROVIDE ENDSELECT ENDTRY ENDWHILE EVENT EVENTS EXEC EXIT EXPORT EXPORTING EXTRACT
 syn keyword abapStatement FETCH FIELDS FORM FORMAT FREE FROM FUNCTION
 syn keyword abapStatement GENERATE GET
 syn keyword abapStatement HIDE
-syn keyword abapStatement IF IMPORT IMPORTING INDEX INFOTYPES INITIAL INITIALIZATION INTERFACE INTERFACES INPUT INSERT IMPLEMENTATION IS
+syn keyword abapStatement IF IMPORT IMPORTING INDEX INFOTYPES INITIALIZATION INTERFACE INTERFACES INPUT INSERT IMPLEMENTATION 
 syn keyword abapStatement LEAVE LIKE LINE LOAD LOCAL LOOP
 syn keyword abapStatement MESSAGE METHOD METHODS MODIFY MODULE MOVE MULTIPLY
 syn keyword abapStatement ON OVERLAY OPTIONAL OTHERS
 syn keyword abapStatement PACK PARAMETERS PERFORM POSITION PROGRAM PROVIDE PUT
-syn keyword abapStatement RAISE RANGES RECEIVE REDEFINITION REFERENCE REFRESH REJECT REPLACE REPORT RESERVE RESTORE RETURNING ROLLBACK
+syn keyword abapStatement RAISE RANGES RECEIVE RECEIVING REDEFINITION REFERENCE REFRESH REJECT REPLACE REPORT RESERVE RESTORE RETURNING ROLLBACK
 syn keyword abapStatement SCAN SCROLL SEARCH SELECT SET SHIFT SKIP SORT SORTED SPLIT STANDARD STATICS STEP STOP SUBMIT SUBTRACT SUM SUMMARY SUPPRESS
 syn keyword abapStatement TABLES TIMES TRANSFER TRANSLATE TRY TYPE TYPES
 syn keyword abapStatement UNASSIGN ULINE UNPACK UPDATE
 syn keyword abapStatement WHEN WHILE WINDOW WRITE
 
 " More statemets
+syn keyword abapStatement LINES
+syn keyword abapStatement INTO GROUP BY HAVING ORDER BY SINGLE
+syn keyword abapStatement APPENDING CORRESPONDING FIELDS OF TABLE
+syn keyword abapStatement LEFT RIGHT OUTER INNER JOIN AS CLIENT SPECIFIED BYPASSING BUFFER ROWS CONNECTING
 syn keyword abapStatement OCCURS STRUCTURE OBJECT PROPERTY
 syn keyword abapStatement CASTING APPEND RAISING VALUE COLOR
 syn keyword abapStatement CHANGING EXCEPTION EXCEPTIONS DEFAULT CHECKBOX COMMENT
 syn keyword abapStatement ID NUMBER FOR TITLE OUTPUT
 
 " Special ABAP specific tables:
-syn match   abapSpecial       "\(\W\|^\)\(sy\|\(p\|pa\)\d\d\d\d\|t\d\d\d.\|innnn\)\(\W\|$\)"ms=s+1,me=e-1
-syn match   abapSpecialTables "\(sy\|\(p\|pa\)\d\d\d\d\|t\d\d\d.\|innnn\)-"me=e-1 contained
-syn match   abapSpecial       "\(\W\|^\)\w\+-\(\w\+-\w\+\|\w\+\)"ms=s+1 contains=abapSpecialTables,abapStatement,abapComplexStatement
+syn match   abapSpecialTables "\<\(sy\|\(p\|pa\)\d\d\d\d\|t\d\d\d.\|innnn\)-"me=e-1 contained
+syn match   abapStructure     "\<\w\+-[^\>]"me=e-2 contains=abapSpecialTables,abapStatement,abapComplexStatement
+syn match   abapField         "-\w\+"ms=s+1
 
 " Pointer
 syn match   abapSpecial  "<\w\+>"
 
-" Abap constants:
+" Abap common constants:
 syn keyword abapSpecial  TRUE FALSE NULL SPACE
 
 " Includes
@@ -155,15 +161,8 @@
 syn keyword abapOperator cosh sinh tanh exp log log10 sqrt
 
 " String operators
-syn keyword abapOperator strlen xstrlen charlen numofchar dbmaxlen
+syn keyword abapStatement strlen xstrlen charlen numofchar dbmaxlen
 
-" Table operators
-syn keyword abapOperator lines
-
-" Table operators (SELECT operators)
-syn keyword abapOperator INTO WHERE GROUP BY HAVING ORDER BY SINGLE
-syn keyword abapOperator APPENDING CORRESPONDING FIELDS OF TABLE
-syn keyword abapOperator LEFT RIGHT OUTER INNER JOIN AS CLIENT SPECIFIED BYPASSING BUFFER UP TO ROWS CONNECTING
 syn keyword abapOperator EQ NE LT LE GT GE NOT AND OR XOR IN LIKE BETWEEN
 
 " An error? Not strictly... but cannot think of reason this is intended.
@@ -193,7 +192,7 @@
   HiLink abapComplexStatement      Statement
   HiLink abapSpecial        Special
   HiLink abapNamespace      Special
-  HiLink abapSpecialTables  PreProc
+  HiLink abapSpecialTables  Special
   HiLink abapSymbolOperator abapOperator
   HiLink abapOperator       Operator
   HiLink abapCharString     String
@@ -201,6 +200,8 @@
   HiLink abapFloat          Float
   HiLink abapTypes          Type
   HiLink abapSymbol         Structure
+  HiLink abapStructure      Structure
+  HiLink abapField          Variable
   HiLink abapNumber         Number
   HiLink abapHex            Number
 
diff --git a/runtime/syntax/lex.vim b/runtime/syntax/lex.vim
index e500f5c..b7aff34 100644
--- a/runtime/syntax/lex.vim
+++ b/runtime/syntax/lex.vim
@@ -1,8 +1,8 @@
 " Vim syntax file
 " Language:	Lex
-" Maintainer:	Charles E. Campbell, Jr. <NdrOchipS@PcampbellAfamily.Mbiz>
-" Last Change:	Nov 01, 2010
-" Version:	12
+" Maintainer:	Charles E. Campbell <NdrOchipS@PcampbellAfamily.Mbiz>
+" Last Change:	Nov 14, 2012
+" Version:	14
 " URL:	http://mysite.verizon.net/astronaut/vim/index.html#vimlinks_syntax
 "
 " Option:
@@ -17,20 +17,16 @@
 endif
 
 " Read the C/C++ syntax to start with
-if version >= 600
-  if exists("lex_uses_cpp")
-    runtime! syntax/cpp.vim
-  else
-    runtime! syntax/c.vim
+let s:Cpath= fnameescape(expand("<sfile>:p:h").(exists("g:lex_uses_cpp")? "/cpp.vim" : "/c.vim"))
+if !filereadable(s:Cpath)
+ for s:Cpath in split(globpath(&rtp,(exists("g:lex_uses_cpp")? "syntax/cpp.vim" : "syntax/c.vim")),"\n")
+  if filereadable(fnameescape(s:Cpath))
+   let s:Cpath= fnameescape(s:Cpath)
+   break
   endif
-  unlet b:current_syntax
-else
-  if exists("lex_uses_cpp")
-    so <sfile>:p:h/cpp.vim
-  else
-    so <sfile>:p:h/c.vim
-  endif
+ endfor
 endif
+exe "syn include @lexCcode ".s:Cpath
 
 " --- ========= ---
 " --- Lex stuff ---
@@ -39,10 +35,6 @@
 " Options Section
 syn match lexOptions '^%\s*option\>.*$' contains=lexPatString
 
-"I'd prefer to use lex.* , but vim doesn't handle forward definitions yet
-syn cluster lexListGroup		contains=lexAbbrvBlock,lexAbbrv,lexAbbrv,lexAbbrvRegExp,lexInclude,lexPatBlock,lexPat,lexBrace,lexPatString,lexPatTag,lexPatTag,lexPatComment,lexPatCodeLine,lexMorePat,lexPatSep,lexSlashQuote,lexPatCode,cInParen,cUserLabel,cOctalZero,cCppSkip,cErrInBracket,cErrInParen,cOctalError,cCppOut2,cCommentStartError,cParenError
-syn cluster lexListPatCodeGroup	contains=lexAbbrvBlock,lexAbbrv,lexAbbrv,lexAbbrvRegExp,lexInclude,lexPatBlock,lexPat,lexBrace,lexPatTag,lexPatTag,lexPatTagZoneStart,lexPatComment,lexPatCodeLine,lexMorePat,lexPatSep,lexSlashQuote,cInParen,cUserLabel,cOctalZero,cCppSkip,cErrInBracket,cErrInParen,cOctalError,cCppOut2,cCommentStartError,cParenError
-
 " Abbreviations Section
 if has("folding")
  syn region lexAbbrvBlock	fold start="^\(\h\+\s\|%{\)"	end="^\ze%%$"	skipnl	nextgroup=lexPatBlock contains=lexAbbrv,lexInclude,lexAbbrvComment,lexStartState
@@ -53,52 +45,69 @@
 syn match  lexAbbrv		"^%[sx]"					contained
 syn match  lexAbbrvRegExp	"\s\S.*$"lc=1				contained nextgroup=lexAbbrv,lexInclude
 if has("folding")
- syn region lexInclude	fold matchgroup=lexSep	start="^%{"	end="%}"	contained	contains=ALLBUT,@lexListGroup
+ syn region lexInclude	fold matchgroup=lexSep	start="^%{"	end="%}"	contained	contains=@lexCcode
  syn region lexAbbrvComment	fold			start="^\s\+/\*"	end="\*/"	contains=@Spell
+ syn region lexAbbrvComment	fold			start="\%^/\*"	end="\*/"	contains=@Spell
  syn region lexStartState	fold matchgroup=lexAbbrv	start="^%\a\+"	end="$"	contained
 else
- syn region lexInclude	matchgroup=lexSep		start="^%{"	end="%}"	contained	contains=ALLBUT,@lexListGroup
+ syn region lexInclude	matchgroup=lexSep		start="^%{"	end="%}"	contained	contains=@lexCcode
  syn region lexAbbrvComment				start="^\s\+/\*"	end="\*/"	contains=@Spell
+ syn region lexAbbrvComment				start="\%^/\*"	end="\*/"	contains=@Spell
  syn region lexStartState	matchgroup=lexAbbrv		start="^%\a\+"	end="$"	contained
 endif
 
 "%% : Patterns {Actions}
 if has("folding")
- syn region lexPatBlock	fold matchgroup=Todo	start="^%%$" matchgroup=Todo	end="^%%$"	skipnl	skipwhite	contains=lexPatTag,lexPatTagZone,lexPatComment,lexPat,lexPatInclude
- syn region lexPat		fold			start=+\S+ skip="\\\\\|\\."	end="\s"me=e-1		contained nextgroup=lexMorePat,lexPatSep contains=lexPatTag,lexPatString,lexSlashQuote,lexBrace
+ syn region lexPatBlock	fold matchgroup=Todo	start="^%%$" matchgroup=Todo	end="^%\ze%$"	skipnl	skipwhite	nextgroup=lexFinalCodeBlock	contains=lexPatTag,lexPatTagZone,lexPatComment,lexPat,lexPatInclude
+ syn region lexPat		fold			start=+\S+ skip="\\\\\|\\."	end="\s"me=e-1	skipwhite	contained nextgroup=lexMorePat,lexPatSep,lexPattern contains=lexPatTag,lexPatString,lexSlashQuote,lexBrace
  syn region lexPatInclude	fold matchgroup=lexSep	start="^%{"	end="%}"	contained	contains=lexPatCode
  syn region lexBrace	fold			start="\[" skip=+\\\\\|\\+	end="]"			contained
  syn region lexPatString	fold matchgroup=String	start=+"+	skip=+\\\\\|\\"+	matchgroup=String end=+"+	contained
 else
- syn region lexPatBlock	matchgroup=Todo		start="^%%$" matchgroup=Todo	end="^%%$"	skipnl	skipwhite	contains=lexPatTag,lexPatTagZone,lexPatComment,lexPat,lexPatInclude
- syn region lexPat					start=+\S+ skip="\\\\\|\\."	end="\s"me=e-1		contained nextgroup=lexMorePat,lexPatSep contains=lexPatTag,lexPatString,lexSlashQuote,lexBrace
+ syn region lexPatBlock	matchgroup=Todo		start="^%%$" matchgroup=Todo	end="^%%$"	skipnl	skipwhite	nextgroup=lexFinalCodeBlock	contains=lexPatTag,lexPatTagZone,lexPatComment,lexPat,lexPatInclude
+ syn region lexPat					start=+\S+ skip="\\\\\|\\."	end="\s"me=e-1	skipwhite	contained nextgroup=lexMorePat,lexPatSep,lexPattern contains=lexPatTag,lexPatString,lexSlashQuote,lexBrace
  syn region lexPatInclude	matchgroup=lexSep		start="^%{"	end="%}"	contained	contains=lexPatCode
  syn region lexBrace				start="\[" skip=+\\\\\|\\+	end="]"			contained
  syn region lexPatString	matchgroup=String		start=+"+	skip=+\\\\\|\\"+	matchgroup=String end=+"+	contained
 endif
 syn match  lexPatTag	"^<\I\i*\(,\I\i*\)*>"			contained nextgroup=lexPat,lexPatTag,lexMorePat,lexPatSep
-syn match  lexPatTagZone	"^<\I\i*\(,\I\i*\)*>\s*\ze{"		contained nextgroup=lexPatTagZoneStart
+syn match  lexPatTagZone	"^<\I\i*\(,\I\i*\)*>\s\+\ze{"			contained nextgroup=lexPatTagZoneStart
 syn match  lexPatTag	+^<\I\i*\(,\I\i*\)*>*\(\\\\\)*\\"+		contained nextgroup=lexPat,lexPatTag,lexMorePat,lexPatSep
+
+" Lex Patterns
+syn region lexPattern	start='[^ \t{}]'	end="$"			contained	contains=lexPatRange
+syn region lexPatRange	matchgroup=Delimiter	start='\['	skip='\\\\\|\\.'	end='\]'	contains=lexEscape
+syn match  lexEscape	'\%(\\\\\)*\\.'				contained
+
 if has("folding")
- syn region  lexPatTagZoneStart matchgroup=lexPatTag	fold	start='{' end='}'	contained contains=lexPat,lexPatComment
+ syn region lexPatTagZoneStart matchgroup=lexPatTag	fold	start='{' end='}'	contained contains=lexPat,lexPatComment
  syn region lexPatComment	start="\s\+/\*" end="\*/"	fold	skipnl	contained contains=cTodo skipwhite nextgroup=lexPatComment,lexPat,@Spell
 else
- syn region  lexPatTagZoneStart matchgroup=lexPatTag		start='{' end='}'	contained contains=lexPat,lexPatComment
+ syn region lexPatTagZoneStart matchgroup=lexPatTag		start='{' end='}'	contained contains=lexPat,lexPatComment
  syn region lexPatComment	start="\s\+/\*" end="\*/"		skipnl	contained contains=cTodo skipwhite nextgroup=lexPatComment,lexPat,@Spell
 endif
-syn match  lexPatCodeLine	".*$"					contained contains=ALLBUT,@lexListGroup
+syn match  lexPatCodeLine	"[^{\[].*"				contained contains=@lexCcode
 syn match  lexMorePat	"\s*|\s*$"			skipnl	contained nextgroup=lexPat,lexPatTag,lexPatComment
 syn match  lexPatSep	"\s\+"					contained nextgroup=lexMorePat,lexPatCode,lexPatCodeLine
 syn match  lexSlashQuote	+\(\\\\\)*\\"+				contained
 if has("folding")
- syn region lexPatCode matchgroup=Delimiter start="{" end="}"	fold	skipnl contained contains=ALLBUT,@lexListPatCodeGroup
+ syn region lexPatCode matchgroup=Delimiter start="{" end="}"	fold	skipnl contained contains=@lexCcode,lexCFunctions
 else
- syn region lexPatCode matchgroup=Delimiter start="{" end="}"		skipnl contained contains=ALLBUT,@lexListPatCodeGroup
+ syn region lexPatCode matchgroup=Delimiter start="{" end="}"	skipnl	contained contains=@lexCcode,lexCFunctions
 endif
 
+" Lex "functions" which may appear in C/C++ code blocks
 syn keyword lexCFunctions	BEGIN	input	unput	woutput	yyleng	yylook	yytext
 syn keyword lexCFunctions	ECHO	output	winput	wunput	yyless	yymore	yywrap
 
+" %%
+"  lexAbbrevBlock
+" %%
+"  lexPatBlock
+" %%
+"  lexFinalCodeBlock
+syn region lexFinalCodeBlock matchgroup=Todo start="%$"me=e-1 end="\%$"	contained	contains=@lexCcode
+
 " <c.vim> includes several ALLBUTs; these have to be treated so as to exclude lex* groups
 syn cluster cParenGroup	add=lex.*
 syn cluster cDefineGroup	add=lex.*
@@ -107,27 +116,27 @@
 
 " Synchronization
 syn sync clear
-syn sync minlines=300
+syn sync minlines=500
 syn sync match lexSyncPat	grouphere  lexPatBlock	"^%[a-zA-Z]"
 syn sync match lexSyncPat	groupthere lexPatBlock	"^<$"
 syn sync match lexSyncPat	groupthere lexPatBlock	"^%%$"
 
 " The default highlighting.
 hi def link lexAbbrvComment	lexPatComment
-hi def link lexBrace	lexPat
-hi def link lexPatTagZone	lexPatTag
-hi def link lexSlashQuote	lexPat
-
 hi def link lexAbbrvRegExp	Macro
 hi def link lexAbbrv	SpecialChar
+hi def link lexBrace	lexPat
 hi def link lexCFunctions	Function
+hi def link lexCstruct	cStructure
 hi def link lexMorePat	SpecialChar
 hi def link lexOptions	PreProc
 hi def link lexPatComment	Comment
 hi def link lexPat		Function
 hi def link lexPatString	Function
 hi def link lexPatTag	Special
+hi def link lexPatTagZone	lexPatTag
 hi def link lexSep		Delimiter
+hi def link lexSlashQuote	lexPat
 hi def link lexStartState	Statement
 
 let b:current_syntax = "lex"
diff --git a/runtime/syntax/progress.vim b/runtime/syntax/progress.vim
index 190a0f3..85a54a6 100644
--- a/runtime/syntax/progress.vim
+++ b/runtime/syntax/progress.vim
@@ -3,13 +3,13 @@
 " Filename extensions:	*.p (collides with Pascal),
 "			*.i (collides with assembler)
 "			*.w (collides with cweb)
-" Maintainer:		Philip Uren	<philuSPAX@ieee.org> Remove SPAX spam block
-" Contributors:         Chris Ruprecht	<chris@ruprecht.org>
-"					Philip Uren		<philu@computer.org>
-"					Mikhail Kuperblum	<mikhail@whasup.com>
-"					John Florian		<jflorian@voyager.net>
-" Version:              12
-" Last Change:		Aug 16 2012
+" Maintainer:		Philip Uren		<philuSPAXY@ieee.org> Remove SPAXY spam block
+" Contributors:         Matthew Stickney	<mtstickneySPAXY@gmail.com>
+" 			Chris Ruprecht		<chrisSPAXY@ruprecht.org>
+"			Mikhail Kuperblum	<mikhailSPAXY@whasup.com>
+"			John Florian		<jflorianSPAXY@voyager.net>
+" Version:              13
+" Last Change:		Nov 11 2012
 
 " For version 5.x: Clear all syntax item
 " For version 6.x: Quit when a syntax file was already loaded
@@ -99,8 +99,8 @@
 " Strings. Handles embedded quotes.
 " Note that, for some reason, Progress doesn't use the backslash, "\"
 " as the escape character; it uses tilde, "~".
-syn region ProgressString	matchgroup=ProgressQuote	start=+"+ end=+"+	skip=+\~'\|\~\~+ contains=@Spell
-syn region ProgressString	matchgroup=ProgressQuote	start=+'+ end=+'+	skip=+\~'\|\~\~+ contains=@Spell
+syn region ProgressString matchgroup=ProgressQuote start=+"+ end=+"+ skip=+\~'\|\~\~\|\~"+ contains=@Spell
+syn region ProgressString matchgroup=ProgressQuote start=+'+ end=+'+ skip=+\~'\|\~\~\|\~"+ contains=@Spell
 
 syn match  ProgressIdentifier		"\<[a-zA-Z_][a-zA-Z0-9_]*\>()"
 
diff --git a/runtime/syntax/rst.vim b/runtime/syntax/rst.vim
index b3f37d4..b680897 100644
--- a/runtime/syntax/rst.vim
+++ b/runtime/syntax/rst.vim
@@ -1,7 +1,7 @@
 " Vim syntax file
 " Language:         reStructuredText documentation format
 " Maintainer:       Nikolai Weibull <now@bitwi.se>
-" Latest Revision:  2012-08-05
+" Latest Revision:  2012-11-01
 
 if exists("b:current_syntax")
   finish
@@ -139,6 +139,27 @@
 " though.
 syn sync minlines=50 linebreaks=1
 
+syn region rstCodeBlock contained matchgroup=rstDirective
+      \ start=+\%(sourcecode\|code\%(-block\)\=\)::\s+
+      \ skip=+^$+
+      \ end=+^\s\@!+ 
+      \ contains=@NoSpell
+syn cluster rstDirectives add=rstCodeBlock
+
+if !exists('g:rst_syntax_code_list')
+    let g:rst_syntax_code_list = ['vim', 'java', 'cpp', 'lisp', 'php', 'python', 'perl']
+endif
+
+for code in g:rst_syntax_code_list
+    unlet! b:current_syntax
+    exe 'syn include @rst'.code.' syntax/'.code.'.vim'
+    exe 'syn region rstDirective'.code.' matchgroup=rstDirective fold '
+                \.'start=#\%(sourcecode\|code\%(-block\)\=\)::\s\+'.code.'\s*$# '
+                \.'skip=#^$# '
+                \.'end=#^\s\@!# contains=@NoSpell,@rst'.code
+    exe 'syn cluster rstDirectives add=rstDirective'.code
+endfor
+
 hi def link rstTodo                         Todo
 hi def link rstComment                      Comment
 hi def link rstSections                     Title
@@ -168,6 +189,7 @@
 hi def link rstCitationReference            Identifier
 hi def link rstHyperLinkReference           Identifier
 hi def link rstStandaloneHyperlink          Identifier
+hi def link rstCodeBlock                    String
 
 let b:current_syntax = "rst"
 
diff --git a/runtime/syntax/sh.vim b/runtime/syntax/sh.vim
index 355e8eb..f3c7604 100644
--- a/runtime/syntax/sh.vim
+++ b/runtime/syntax/sh.vim
@@ -1,9 +1,9 @@
 " Vim syntax file
 " Language:		shell (sh) Korn shell (ksh) bash (sh)
-" Maintainer:		Dr. Charles E. Campbell, Jr.  <NdrOchipS@PcampbellAfamily.Mbiz>
+" Maintainer:		Charles E. Campbell  <NdrOchipS@PcampbellAfamily.Mbiz>
 " Previous Maintainer:	Lennart Schultz <Lennart.Schultz@ecmwf.int>
-" Last Change:		Mar 19, 2012
-" Version:		122
+" Last Change:		Nov 14, 2012
+" Version:		128
 " URL:		http://mysite.verizon.net/astronaut/vim/index.html#vimlinks_syntax
 " For options and settings, please use:      :help ft-sh-syntax
 " This file includes many ideas from ?ric Brunet (eric.brunet@ens.fr)
@@ -17,15 +17,18 @@
 endif
 
 " AFAICT "." should be considered part of the iskeyword.  Using iskeywords in
-" syntax is dicey, so the following code permits the user to prevent/override
-" its setting.
-if exists("g:sh_isk")          " override support
- exe "setlocal isk=".g:sh_isk
-elseif !exists("g:sh_noisk")   " prevent modification support
- setlocal isk+=.
+" syntax is dicey, so the following code permits the user to
+"  g:sh_isk set to a string	: specify iskeyword.
+"  g:sh_noisk exists	: don't change iskeyword
+"  g:sh_noisk does not exist	: (default) append "." to iskeyword
+if exists("g:sh_isk") && type(g:sh_isk) == 1	" user specifying iskeyword
+ exe "setl isk=".g:sh_isk
+elseif !exists("g:sh_noisk")		" optionally prevent appending '.' to iskeyword
+ setl isk+=.
 endif
 
 " trying to answer the question: which shell is /bin/sh, really?
+" If the user has not specified any of g:is_kornshell, g:is_bash, g:is_posix, g:is_sh, then guess.
 if !exists("g:is_kornshell") && !exists("g:is_bash") && !exists("g:is_posix") && !exists("g:is_sh")
  if executable("/bin/sh")
   if     resolve("/bin/sh") =~ 'bash$'
@@ -76,16 +79,19 @@
  echomsg "Ignoring g:sh_fold_enabled=".g:sh_fold_enabled."; need to re-compile vim for +fold support"
 endif
 if !exists("s:sh_fold_functions")
- let s:sh_fold_functions = 1
+ let s:sh_fold_functions= and(g:sh_fold_enabled,1)
 endif
 if !exists("s:sh_fold_heredoc")
- let s:sh_fold_heredoc   = 2
+ let s:sh_fold_heredoc  = and(g:sh_fold_enabled,2)
 endif
 if !exists("s:sh_fold_ifdofor")
- let s:sh_fold_ifdofor   = 4
+ let s:sh_fold_ifdofor  = and(g:sh_fold_enabled,4)
 endif
 if g:sh_fold_enabled && &fdm == "manual"
- setlocal fdm=syntax
+ " Given that	the	user provided g:sh_fold_enabled
+ " 	AND	g:sh_fold_enabled is manual (usual default)
+ " 	implies	a desire for syntax-based folding
+ setl fdm=syntax
 endif
 
 " sh syntax is case sensitive {{{1
@@ -102,12 +108,12 @@
 syn cluster shCaseEsacList	contains=shCaseStart,shCase,shCaseBar,shCaseIn,shComment,shDeref,shDerefSimple,shCaseCommandSub,shCaseExSingleQuote,shCaseSingleQuote,shCaseDoubleQuote,shCtrlSeq,@shErrorList,shStringSpecial,shCaseRange
 syn cluster shCaseList	contains=@shCommandSubList,shCaseEsac,shColon,shCommandSub,shComment,shDo,shEcho,shExpr,shFor,shHereDoc,shIf,shRedir,shSetList,shSource,shStatement,shVariable,shCtrlSeq
 "syn cluster shColonList	contains=@shCaseList
-syn cluster shCommandSubList	contains=shArithmetic,shDeref,shDerefSimple,shEscape,shNumber,shOperator,shPosnParm,shExSingleQuote,shSingleQuote,shExDoubleQuote,shDoubleQuote,shStatement,shVariable,shSubSh,shAlias,shTest,shCtrlSeq,shSpecial
+syn cluster shCommandSubList	contains=shArithmetic,shDeref,shDerefSimple,shEscape,shNumber,shOperator,shPosnParm,shExSingleQuote,shSingleQuote,shExDoubleQuote,shDoubleQuote,shStatement,shVariable,shSubSh,shAlias,shTest,shCtrlSeq,shSpecial,shCmdParenRegion
 syn cluster shCurlyList	contains=shNumber,shComma,shDeref,shDerefSimple,shDerefSpecial
-syn cluster shDblQuoteList	contains=shCommandSub,shDeref,shDerefSimple,shPosnParm,shCtrlSeq,shSpecial
+syn cluster shDblQuoteList	contains=shCommandSub,shDeref,shDerefSimple,shEscape,shPosnParm,shCtrlSeq,shSpecial
 syn cluster shDerefList	contains=shDeref,shDerefSimple,shDerefVar,shDerefSpecial,shDerefWordError,shDerefPPS
 syn cluster shDerefVarList	contains=shDerefOp,shDerefVarArray,shDerefOpError
-syn cluster shEchoList	contains=shArithmetic,shCommandSub,shDeref,shDerefSimple,shExpr,shExSingleQuote,shExDoubleQuote,shSingleQuote,shDoubleQuote,shCtrlSeq,shEchoQuote
+syn cluster shEchoList	contains=shArithmetic,shCommandSub,shDeref,shDerefSimple,shEscape,shExpr,shExSingleQuote,shExDoubleQuote,shSingleQuote,shDoubleQuote,shCtrlSeq,shEchoQuote
 syn cluster shExprList1	contains=shCharClass,shNumber,shOperator,shExSingleQuote,shExDoubleQuote,shSingleQuote,shDoubleQuote,shExpr,shDblBrace,shDeref,shDerefSimple,shCtrlSeq
 syn cluster shExprList2	contains=@shExprList1,@shCaseList,shTest
 syn cluster shFunctionList	contains=@shCommandSubList,shCaseEsac,shColon,shCommandSub,shComment,shDo,shEcho,shExpr,shFor,shHereDoc,shIf,shOption,shRedir,shSetList,shSource,shStatement,shVariable,shOperator,shCtrlSeq
@@ -160,7 +166,7 @@
 
 " Options: {{{1
 " ====================
-syn match   shOption	"\s\zs[-+][-_a-zA-Z0-9]\+\>"
+syn match   shOption	"\s\zs[-+][-_a-zA-Z0-9#]\+"
 syn match   shOption	"\s\zs--[^ \t$`'"|]\+"
 
 " File Redirection Highlighted As Operators: {{{1
@@ -204,14 +210,15 @@
 
 " Loops: do, if, while, until {{{1
 " ======
-if (g:sh_fold_enabled % (s:sh_fold_ifdofor * 2))/s:sh_fold_ifdofor
+if s:sh_fold_ifdofor
  syn region shDo	fold transparent matchgroup=shConditional start="\<do\>" matchgroup=shConditional end="\<done\>" contains=@shLoopList
  syn region shIf	fold transparent matchgroup=shConditional start="\<if\_s" matchgroup=shConditional skip=+-fi\>+ end="\<;\_s*then\>" end="\<fi\>"   contains=@shIfList
- syn region shFor	fold matchgroup=shLoop start="\<for\_s" end="\<in\_s" end="\<do\>"me=e-2	contains=@shLoopList,shDblParen skipwhite nextgroup=shCurlyIn
+ syn region shFor	fold matchgroup=shLoop start="\<for\ze\_s\s*\%(((\)\@!" end="\<in\_s" end="\<do\>"me=e-2	contains=@shLoopList,shDblParen skipwhite nextgroup=shCurlyIn
 else
  syn region shDo	transparent matchgroup=shConditional start="\<do\>" matchgroup=shConditional end="\<done\>" contains=@shLoopList
  syn region shIf	transparent matchgroup=shConditional start="\<if\_s" matchgroup=shConditional skip=+-fi\>+ end="\<;\_s*then\>" end="\<fi\>"   contains=@shIfList
- syn region shFor	matchgroup=shLoop start="\<for\_s" end="\<in\>" end="\<do\>"me=e-2	contains=@shLoopList,shDblParen skipwhite nextgroup=shCurlyIn
+ syn region shFor	matchgroup=shLoop start="\<for\ze\_s\s*\%(((\)\@!" end="\<in\>" end="\<do\>"me=e-2	contains=@shLoopList,shDblParen skipwhite nextgroup=shCurlyIn
+ syn match  shForPP	'\<for\>\ze\_s*(('
 endif
 if exists("b:is_kornshell") || exists("b:is_bash")
  syn cluster shCaseList	add=shRepeat
@@ -230,7 +237,7 @@
 " ====
 syn match   shCaseBar	contained skipwhite "\(^\|[^\\]\)\(\\\\\)*\zs|"		nextgroup=shCase,shCaseStart,shCaseBar,shComment,shCaseExSingleQuote,shCaseSingleQuote,shCaseDoubleQuote
 syn match   shCaseStart	contained skipwhite skipnl "("			nextgroup=shCase,shCaseBar
-if (g:sh_fold_enabled % (s:sh_fold_ifdofor * 2))/s:sh_fold_ifdofor
+if s:sh_fold_ifdofor
  syn region  shCase	fold contained skipwhite skipnl matchgroup=shSnglCase start="\%(\\.\|[^#$()'" \t]\)\{-}\zs)"  end=";;" end="esac"me=s-1 contains=@shCaseList nextgroup=shCaseStart,shCase,shComment
  syn region  shCaseEsac	fold matchgroup=shConditional start="\<case\>" end="\<esac\>"	contains=@shCaseEsacList
 else
@@ -246,13 +253,17 @@
 syn region  shCaseSingleQuote	matchgroup=shQuote start=+'+ end=+'+		contains=shStringSpecial		skipwhite skipnl nextgroup=shCaseBar	contained
 syn region  shCaseDoubleQuote	matchgroup=shQuote start=+"+ skip=+\\\\\|\\.+ end=+"+	contains=@shDblQuoteList,shStringSpecial	skipwhite skipnl nextgroup=shCaseBar	contained
 syn region  shCaseCommandSub	start=+`+ skip=+\\\\\|\\.+ end=+`+		contains=@shCommandSubList		skipwhite skipnl nextgroup=shCaseBar	contained
-syn region  shCaseRange	matchgroup=Delimiter start=+\[+ skip=+\\\\+ end=+]+	contained
-
+if exists("b:is_bash")
+ syn region  shCaseRange	matchgroup=Delimiter start=+\[+ skip=+\\\\+ end=+\]+	contained	contains=shCharClass
+ syn match   shCharClass	'\[:\%(alnum\|alpha\|ascii\|blank\|cntrl\|digit\|graph\|lower\|print\|punct\|space\|upper\|word\|or\|xdigit\):\]'			contained
+else
+ syn region  shCaseRange	matchgroup=Delimiter start=+\[+ skip=+\\\\+ end=+\]+	contained
+endif
 " Misc: {{{1
 "======
 syn match   shWrapLineOperator "\\$"
-syn region  shCommandSub   start="`" skip="\\\\\|\\." end="`" contains=@shCommandSubList
-syn match   shEscape	contained	'\\.'         contains=@shCommandSubList
+syn region  shCommandSub   start="`" skip="\\\\\|\\." end="`"	contains=@shCommandSubList
+syn match   shEscape	contained	'\%(\\\\\)*\\.'
 
 " $() and $(()): {{{1
 " $(..) is not supported by sh (Bourne shell).  However, apparently
@@ -268,20 +279,23 @@
 elseif !exists("g:sh_no_error")
  syn region shCommandSub matchgroup=Error start="\$(" end=")" contains=@shCommandSubList
 endif
+syn region shCmdParenRegion matchgroup=shCmdSubRegion start="(" skip='\\\\\|\\.' end=")"	contains=@shCommandSubList
 
 if exists("b:is_bash")
  syn cluster shCommandSubList add=bashSpecialVariables,bashStatement
  syn cluster shCaseList add=bashAdminStatement,bashStatement
  syn keyword bashSpecialVariables contained auto_resume BASH BASH_ALIASES BASH_ALIASES BASH_ARGC BASH_ARGC BASH_ARGV BASH_ARGV BASH_CMDS BASH_CMDS BASH_COMMAND BASH_COMMAND BASH_ENV BASH_EXECUTION_STRING BASH_EXECUTION_STRING BASH_LINENO BASH_LINENO BASHOPTS BASHOPTS BASHPID BASHPID BASH_REMATCH BASH_REMATCH BASH_SOURCE BASH_SOURCE BASH_SUBSHELL BASH_SUBSHELL BASH_VERSINFO BASH_VERSION BASH_XTRACEFD BASH_XTRACEFD CDPATH COLUMNS COLUMNS COMP_CWORD COMP_CWORD COMP_KEY COMP_KEY COMP_LINE COMP_LINE COMP_POINT COMP_POINT COMPREPLY COMPREPLY COMP_TYPE COMP_TYPE COMP_WORDBREAKS COMP_WORDBREAKS COMP_WORDS COMP_WORDS COPROC COPROC DIRSTACK EMACS EMACS ENV ENV EUID FCEDIT FIGNORE FUNCNAME FUNCNAME FUNCNEST FUNCNEST GLOBIGNORE GROUPS histchars HISTCMD HISTCONTROL HISTFILE HISTFILESIZE HISTIGNORE HISTSIZE HISTTIMEFORMAT HISTTIMEFORMAT HOME HOSTFILE HOSTNAME HOSTTYPE IFS IGNOREEOF INPUTRC LANG LC_ALL LC_COLLATE LC_CTYPE LC_CTYPE LC_MESSAGES LC_NUMERIC LC_NUMERIC LINENO LINES LINES MACHTYPE MAIL MAILCHECK MAILPATH MAPFILE MAPFILE OLDPWD OPTARG OPTERR OPTIND OSTYPE PATH PIPESTATUS POSIXLY_CORRECT POSIXLY_CORRECT PPID PROMPT_COMMAND PS1 PS2 PS3 PS4 PWD RANDOM READLINE_LINE READLINE_LINE READLINE_POINT READLINE_POINT REPLY SECONDS SHELL SHELL SHELLOPTS SHLVL TIMEFORMAT TIMEOUT TMPDIR TMPDIR UID
- syn keyword bashStatement chmod clear complete du egrep expr fgrep find gnufind gnugrep grep install less ls mkdir mv rm rmdir rpm sed sleep sort strip tail touch
+ syn keyword bashStatement chmod clear complete du egrep expr fgrep find gnufind gnugrep grep less ls mkdir mv rm rmdir rpm sed sleep sort strip tail touch
  syn keyword bashAdminStatement daemon killall killproc nice reload restart start status stop
+ syn keyword bashStatement	command compgen
 endif
 
 if exists("b:is_kornshell")
  syn cluster shCommandSubList add=kshSpecialVariables,kshStatement
  syn cluster shCaseList add=kshStatement
  syn keyword kshSpecialVariables contained CDPATH COLUMNS EDITOR ENV ERRNO FCEDIT FPATH HISTFILE HISTSIZE HOME IFS LINENO LINES MAIL MAILCHECK MAILPATH OLDPWD OPTARG OPTIND PATH PPID PS1 PS2 PS3 PS4 PWD RANDOM REPLY SECONDS SHELL TMOUT VISUAL
- syn keyword kshStatement cat chmod clear cp du egrep expr fgrep find grep install killall less ls mkdir mv nice printenv rm rmdir sed sort strip stty tail touch tput
+ syn keyword kshStatement cat chmod clear cp du egrep expr fgrep find grep killall less ls mkdir mv nice printenv rm rmdir sed sort strip stty tail touch tput
+ syn keyword kshStatement command setgroups setsenv
 endif
 
 syn match   shSource	"^\.\s"
@@ -309,8 +323,8 @@
 "syn region  shDoubleQuote	matchgroup=shQuote start=+"+ skip=+\\"+ end=+"+	contains=@shDblQuoteList,shStringSpecial,@Spell
 syn match   shStringSpecial	"[^[:print:] \t]"	contained
 syn match   shStringSpecial	"\%(\\\\\)*\\[\\"'`$()#]"
-syn match   shSpecial	"[^\\]\zs\%(\\\\\)*\\[\\"'`$()#]" nextgroup=shMoreSpecial
-syn match   shSpecial	"^\%(\\\\\)*\\[\\"'`$()#]"
+syn match   shSpecial	"[^\\]\zs\%(\\\\\)*\\[\\"'`$()#]" nextgroup=shMoreSpecial,shComment
+syn match   shSpecial	"^\%(\\\\\)*\\[\\"'`$()#]"	nextgroup=shComment
 syn match   shMoreSpecial	"\%(\\\\\)*\\[\\"'`$()#]" nextgroup=shMoreSpecial contained
 
 " Comments: {{{1
@@ -319,6 +333,7 @@
 syn keyword	shTodo	contained		COMBAK FIXME TODO XXX
 syn match	shComment		"^\s*\zs#.*$"	contains=@shCommentGroup
 syn match	shComment		"\s\zs#.*$"	contains=@shCommentGroup
+syn match	shComment	contained	"#.*$"	contains=@shCommentGroup
 syn match	shQuickComment	contained	"#.*$"
 
 " Here Documents: {{{1
@@ -331,52 +346,52 @@
  syn region shHereDoc matchgroup=shRedir start="<<\s*\**\.\**"	matchgroup=shRedir	end="^\.$"	contains=@shDblQuoteList
  syn region shHereDoc matchgroup=shRedir start="<<-\s*\**\.\**"	matchgroup=shRedir	end="^\s*\.$"	contains=@shDblQuoteList
 
-elseif (g:sh_fold_enabled % (s:sh_fold_heredoc * 2))/s:sh_fold_heredoc
- syn region shHereDoc matchgroup=shRedir fold start="<<\s*\z(\S*\)"		matchgroup=shRedir end="^\z1\s*$"	contains=@shDblQuoteList
- syn region shHereDoc matchgroup=shRedir fold start="<<\s*\"\z(\S*\)\""		matchgroup=shRedir end="^\z1\s*$"
- syn region shHereDoc matchgroup=shRedir fold start="<<\s*'\z(\S*\)'"		matchgroup=shRedir end="^\z1\s*$"
- syn region shHereDoc matchgroup=shRedir fold start="<<-\s*\z(\S*\)"		matchgroup=shRedir end="^\s*\z1\s*$"	contains=@shDblQuoteList
- syn region shHereDoc matchgroup=shRedir fold start="<<-\s*\"\z(\S*\)\""		matchgroup=shRedir end="^\s*\z1\s*$"
- syn region shHereDoc matchgroup=shRedir fold start="<<-\s*'\z(\S*\)'"		matchgroup=shRedir end="^\s*\z1\s*$"
- syn region shHereDoc matchgroup=shRedir fold start="<<\s*\\\_$\_s*\z(\S*\)"		matchgroup=shRedir end="^\z1\s*$"
- syn region shHereDoc matchgroup=shRedir fold start="<<\s*\\\_$\_s*\"\z(\S*\)\""	matchgroup=shRedir end="^\z1\s*$"
- syn region shHereDoc matchgroup=shRedir fold start="<<-\s*\\\_$\_s*'\z(\S*\)'"		matchgroup=shRedir end="^\s*\z1\s*$"
- syn region shHereDoc matchgroup=shRedir fold start="<<-\s*\\\_$\_s*\z(\S*\)"		matchgroup=shRedir end="^\s*\z1\s*$"
- syn region shHereDoc matchgroup=shRedir fold start="<<-\s*\\\_$\_s*\"\z(\S*\)\""	matchgroup=shRedir end="^\s*\z1\s*$"
- syn region shHereDoc matchgroup=shRedir fold start="<<\s*\\\_$\_s*'\z(\S*\)'"		matchgroup=shRedir end="^\z1\s*$"
- syn region shHereDoc matchgroup=shRedir fold start="<<\\\z(\S*\)"		matchgroup=shRedir end="^\z1\s*$"
+elseif s:sh_fold_heredoc
+ syn region shHereDoc matchgroup=shRedir fold start="<<\s*\z([^ \t|]*\)"		matchgroup=shRedir end="^\z1\s*$"	contains=@shDblQuoteList
+ syn region shHereDoc matchgroup=shRedir fold start="<<\s*\"\z([^ \t|]*\)\""		matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir fold start="<<\s*'\z([^ \t|]*\)'"		matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir fold start="<<-\s*\z([^ \t|]*\)"		matchgroup=shRedir end="^\s*\z1\s*$"	contains=@shDblQuoteList
+ syn region shHereDoc matchgroup=shRedir fold start="<<-\s*\"\z([^ \t|]*\)\""		matchgroup=shRedir end="^\s*\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir fold start="<<-\s*'\z([^ \t|]*\)'"		matchgroup=shRedir end="^\s*\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir fold start="<<\s*\\\_$\_s*\z([^ \t|]*\)"	matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir fold start="<<\s*\\\_$\_s*\"\z([^ \t|]*\)\""	matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir fold start="<<-\s*\\\_$\_s*'\z([^ \t|]*\)'"	matchgroup=shRedir end="^\s*\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir fold start="<<-\s*\\\_$\_s*\z([^ \t|]*\)"	matchgroup=shRedir end="^\s*\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir fold start="<<-\s*\\\_$\_s*\"\z([^ \t|]*\)\""	matchgroup=shRedir end="^\s*\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir fold start="<<\s*\\\_$\_s*'\z([^ \t|]*\)'"	matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir fold start="<<\\\z([^ \t|]*\)"		matchgroup=shRedir end="^\z1\s*$"
 
 else
- syn region shHereDoc matchgroup=shRedir start="<<\s*\\\=\z(\S*\)"	matchgroup=shRedir end="^\z1\s*$"    contains=@shDblQuoteList
- syn region shHereDoc matchgroup=shRedir start="<<\s*\"\z(\S*\)\""	matchgroup=shRedir end="^\z1\s*$"
- syn region shHereDoc matchgroup=shRedir start="<<-\s*\z(\S*\)"		matchgroup=shRedir end="^\s*\z1\s*$" contains=@shDblQuoteList
- syn region shHereDoc matchgroup=shRedir start="<<-\s*'\z(\S*\)'"	matchgroup=shRedir end="^\s*\z1\s*$"
- syn region shHereDoc matchgroup=shRedir start="<<\s*'\z(\S*\)'"	matchgroup=shRedir end="^\z1\s*$"
- syn region shHereDoc matchgroup=shRedir start="<<-\s*\"\z(\S*\)\""	matchgroup=shRedir end="^\s*\z1\s*$"
- syn region shHereDoc matchgroup=shRedir start="<<\s*\\\_$\_s*\z(\S*\)"	matchgroup=shRedir end="^\z1\s*$"
- syn region shHereDoc matchgroup=shRedir start="<<-\s*\\\_$\_s*\z(\S*\)"	matchgroup=shRedir end="^\s*\z1\s*$"
- syn region shHereDoc matchgroup=shRedir start="<<-\s*\\\_$\_s*'\z(\S*\)'"	matchgroup=shRedir end="^\s*\z1\s*$"
- syn region shHereDoc matchgroup=shRedir start="<<\s*\\\_$\_s*'\z(\S*\)'"	matchgroup=shRedir end="^\z1\s*$"
- syn region shHereDoc matchgroup=shRedir start="<<\s*\\\_$\_s*\"\z(\S*\)\""	matchgroup=shRedir end="^\z1\s*$"
- syn region shHereDoc matchgroup=shRedir start="<<-\s*\\\_$\_s*\"\z(\S*\)\""	matchgroup=shRedir end="^\s*\z1\s*$"
- syn region shHereDoc matchgroup=shRedir start="<<\\\z(\S*\)"		matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<\s*\\\=\z([^ \t|]*\)"		matchgroup=shRedir end="^\z1\s*$"    contains=@shDblQuoteList
+ syn region shHereDoc matchgroup=shRedir start="<<\s*\"\z([^ \t|]*\)\""		matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<-\s*\z([^ \t|]*\)"		matchgroup=shRedir end="^\s*\z1\s*$" contains=@shDblQuoteList
+ syn region shHereDoc matchgroup=shRedir start="<<-\s*'\z([^ \t|]*\)'"		matchgroup=shRedir end="^\s*\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<\s*'\z([^ \t|]*\)'"		matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<-\s*\"\z([^ \t|]*\)\""		matchgroup=shRedir end="^\s*\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<\s*\\\_$\_s*\z([^ \t|]*\)"		matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<-\s*\\\_$\_s*\z([^ \t|]*\)"		matchgroup=shRedir end="^\s*\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<-\s*\\\_$\_s*'\z([^ \t|]*\)'"		matchgroup=shRedir end="^\s*\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<\s*\\\_$\_s*'\z([^ \t|]*\)'"		matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<\s*\\\_$\_s*\"\z([^ \t|]*\)\""	matchgroup=shRedir end="^\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<-\s*\\\_$\_s*\"\z([^ \t|]*\)\""	matchgroup=shRedir end="^\s*\z1\s*$"
+ syn region shHereDoc matchgroup=shRedir start="<<\\\z([^ \t|]*\)"		matchgroup=shRedir end="^\z1\s*$"
 endif
 
 " Here Strings: {{{1
 " =============
 " available for: bash; ksh (really should be ksh93 only) but not if its a posix
 if exists("b:is_bash") || (exists("b:is_kornshell") && !exists("g:is_posix"))
- syn match shRedir "<<<"
+ syn match shRedir "<<<"	skipwhite	nextgroup=shCmdParenRegion
 endif
 
 " Identifiers: {{{1
 "=============
 syn match  shSetOption	"\s\zs[-+][a-zA-Z0-9]\+\>"	contained
 syn match  shVariable	"\<\([bwglsav]:\)\=[a-zA-Z0-9.!@_%+,]*\ze="	nextgroup=shSetIdentifier
-syn match  shSetIdentifier	"="		contained	nextgroup=shPattern,shDeref,shDerefSimple,shDoubleQuote,shExDoubleQuote,shSingleQuote,shExSingleQuote
+syn match  shSetIdentifier	"="		contained	nextgroup=shCmdParenRegion,shPattern,shDeref,shDerefSimple,shDoubleQuote,shExDoubleQuote,shSingleQuote,shExSingleQuote
 if exists("b:is_bash")
  syn region shSetList oneline matchgroup=shSet start="\<\(declare\|typeset\|local\|export\|unset\)\>\ze[^/]" end="$"	matchgroup=shSetListDelim end="\ze[}|);&]" matchgroup=NONE end="\ze\s\+#\|=" contains=@shIdList
- syn region shSetList oneline matchgroup=shSet start="\<set\>\ze[^/]" end="\ze[;|)]\|$"			matchgroup=shSetListDelim end="\ze[}|);&]" matchgroup=NONE end="\ze\s\+[#=]" contains=@shIdList
+ syn region shSetList oneline matchgroup=shSet start="\<set\>\ze[^/]" end="\ze[;|)]\|$"			matchgroup=shSetListDelim end="\ze[}|);&]" matchgroup=NONE end="\ze\s\+=" contains=@shIdList
 elseif exists("b:is_kornshell")
  syn region shSetList oneline matchgroup=shSet start="\<\(typeset\|export\|unset\)\>\ze[^/]" end="$"		matchgroup=shSetListDelim end="\ze[}|);&]" matchgroup=NONE end="\ze\s\+[#=]" contains=@shIdList
  syn region shSetList oneline matchgroup=shSet start="\<set\>\ze[^/]" end="$"				matchgroup=shSetListDelim end="\ze[}|);&]" matchgroup=NONE end="\ze\s\+[#=]" contains=@shIdList
@@ -390,15 +405,15 @@
 endif
 
 if exists("b:is_bash")
- if (g:sh_fold_enabled % (s:sh_fold_functions * 2))/s:sh_fold_functions
-  syn region shFunctionOne fold	matchgroup=shFunction start="^\s*\h[-a-zA-Z_0-9]*\s*()\_s*{" end="}"	contains=@shFunctionList			skipwhite skipnl nextgroup=shFunctionStart,shQuickComment
+ if s:sh_fold_functions
+  syn region shFunctionOne fold	matchgroup=shFunction start="^\s*\h[-a-zA-Z_0-9]*\s*()\_s*{"	end="}"	contains=@shFunctionList			skipwhite skipnl nextgroup=shFunctionStart,shQuickComment
   syn region shFunctionTwo fold	matchgroup=shFunction start="\h[-a-zA-Z_0-9]*\s*\%(()\)\=\_s*{"	end="}"	contains=shFunctionKey,@shFunctionList contained	skipwhite skipnl nextgroup=shFunctionStart,shQuickComment
  else
   syn region shFunctionOne	matchgroup=shFunction start="^\s*\h[-a-zA-Z_0-9]*\s*()\_s*{"	end="}"	contains=@shFunctionList
   syn region shFunctionTwo	matchgroup=shFunction start="\h[-a-zA-Z_0-9]*\s*\%(()\)\=\_s*{"	end="}"	contains=shFunctionKey,@shFunctionList contained
  endif
 else
- if (g:sh_fold_enabled % (s:sh_fold_functions * 2))/s:sh_fold_functions
+ if s:sh_fold_functions
   syn region shFunctionOne fold	matchgroup=shFunction start="^\s*\h\w*\s*()\_s*{" end="}"	contains=@shFunctionList			skipwhite skipnl nextgroup=shFunctionStart,shQuickComment
   syn region shFunctionTwo fold	matchgroup=shFunction start="\h\w*\s*\%(()\)\=\_s*{"	end="}"	contains=shFunctionKey,@shFunctionList contained	skipwhite skipnl nextgroup=shFunctionStart,shQuickComment
  else
@@ -409,7 +424,7 @@
 
 " Parameter Dereferencing: {{{1
 " ========================
-syn match  shDerefSimple	"\$\%(\h\w*\|\d\)"
+syn match  shDerefSimple	"\$\%(\k\+\|\d\)"
 syn region shDeref	matchgroup=PreProc start="\${" end="}"	contains=@shDerefList,shDerefVarArray
 if !exists("g:sh_no_error")
  syn match  shDerefWordError	"[^}$[]"	contained
@@ -425,12 +440,12 @@
 " ====================================
 if exists("b:is_bash")
  syn region shDeref	matchgroup=PreProc start="\${!" end="\*\=}"	contains=@shDerefList,shDerefOp
- syn match  shDerefVar	contained	"{\@<=!\w\+"		nextgroup=@shDerefVarList
+ syn match  shDerefVar	contained	"{\@<=!\k\+"		nextgroup=@shDerefVarList
 endif
 
 syn match  shDerefSpecial	contained	"{\@<=[-*@?0]"		nextgroup=shDerefOp,shDerefOpError
 syn match  shDerefSpecial	contained	"\({[#!]\)\@<=[[:alnum:]*@_]\+"	nextgroup=@shDerefVarList,shDerefOp
-syn match  shDerefVar	contained	"{\@<=\w\+"		nextgroup=@shDerefVarList
+syn match  shDerefVar	contained	"{\@<=\k\+"		nextgroup=@shDerefVarList
 
 " sh ksh bash : ${var[... ]...}  array reference: {{{1
 syn region  shDerefVarArray   contained	matchgroup=shDeref start="\[" end="]"	contains=@shCommandSubList nextgroup=shDerefOp,shDerefOpError
@@ -477,12 +492,12 @@
  " bash : ${parameter//pattern/string}
  " bash : ${parameter//pattern}
  syn match  shDerefPPS	contained	'/\{1,2}'	nextgroup=shDerefPPSleft
- syn region shDerefPPSleft	contained	start='.'	skip=@\%(\\\)\/@ matchgroup=shDerefOp end='/' end='\ze}' nextgroup=shDerefPPSright contains=@shCommandSubList
- syn region shDerefPPSright	contained	start='.'	end='\ze}'	contains=@shCommandSubList
+ syn region shDerefPPSleft	contained	start='.'	skip=@\%(\\\\\)*\\/@ matchgroup=shDerefOp	end='/' end='\ze}' nextgroup=shDerefPPSright contains=@shCommandSubList
+ syn region shDerefPPSright	contained	start='.'	skip=@\%(\\\\\)\+@		end='\ze}'	contains=@shCommandSubList
 endif
 
 " Arithmetic Parenthesized Expressions: {{{1
-syn region shParen matchgroup=shArithRegion start='(\%(\ze[^(]\|$\)' end=')' contains=@shArithParenList
+syn region shParen matchgroup=shArithRegion start='[^$]\zs(\%(\ze[^(]\|$\)' end=')' contains=@shArithParenList
 
 " Useful sh Keywords: {{{1
 " ===================
@@ -557,6 +572,7 @@
 hi def link shEcho	shString
 hi def link shEchoDelim	shOperator
 hi def link shEchoQuote	shString
+hi def link shForPP	shLoop
 hi def link shEmbeddedEcho	shString
 hi def link shEscape	shCommandSub
 hi def link shExDoubleQuote	shDoubleQuote
@@ -592,6 +608,7 @@
   hi def link bashStatement		shStatement
   hi def link shFunctionParen		Delimiter
   hi def link shFunctionDelim		Delimiter
+  hi def link shCharClass		shSpecial
 endif
 if exists("b:is_kornshell")
   hi def link kshSpecialVariables	shShellVariables
diff --git a/runtime/syntax/sqlhana.vim b/runtime/syntax/sqlhana.vim
new file mode 100644
index 0000000..1410e99
--- /dev/null
+++ b/runtime/syntax/sqlhana.vim
@@ -0,0 +1,293 @@
+" Vim syntax file
+" Language:    SQL, SAP HANA In Memory Database
+" Maintainer:  David Fishburn <dfishburn dot vim at gmail dot com>
+" Last Change: 2012 Oct 23
+" Version:     SP4 b (Q2 2012)
+" Homepage:    http://www.vim.org/scripts/script.php?script_id=4275
+
+" Description: Updated to SAP HANA SP4
+"
+" For version 5.x: Clear all syntax items
+" For version 6.x: Quit when a syntax file was already loaded
+if version < 600
+    syntax clear
+elseif exists("b:current_syntax")
+    finish
+endif
+
+syn case ignore
+
+" The SQL reserved words, defined as keywords.
+" These were pulled from the following SQL reference:
+"     http://help.sap.com/hana/hana_sql_en.pdf
+" An easy approach is to copy all text from the PDF
+" into a Vim buffer.  The keywords are in UPPER case,
+" so you can run the following commands to be left with
+" mainly the UPPER case words:
+"   1.  Delete all words that do not begin with a Capital
+"       %s/\(\<[^A-Z]\w*\>\)//g
+"   2.  Remove all words where the 2nd letter is not a Capital
+"       %s/\(\<[A-Z][^A-Z]\w*\>\)//g
+"   3.  Remove all non-word (or space) characters
+"       %s/[^0-9A-Za-z_ ]*//g
+"   4.  Remove some known words
+"       %s/\<\(SAP\|HANA\|OK\|AG\|IBM\|DB2\|AIX\|POWER\d\+\|UNIX\)\>//g
+"   5.  Remove blank lines and trailing spaces
+"       %s/\s\+$//g
+"       %s/^\s\+//g
+"       %s/^$\n//g
+"   6.  Convert spaces to newlines remove single character
+"       %s/[ ]\+/\r/g
+"       %g/^\w$/d
+"   7.  Sort and remove duplicates
+"       :sort
+"       :Uniq
+"   8.  Use the WhatsMissing plugin against the sqlhana.vim file.
+"   9.  Generated a file of all UPPER cased words which should not
+"       be in the syntax file.  These items should be removed
+"       from the list in step 7.  You can use WhatsNotMissing
+"       between step 7 and this new file to weed out the words
+"       we know are not syntax related.
+"  10.  Use the WhatsMissingRemoveMatches to remove the words
+"       from step 9.
+
+syn keyword sqlSpecial  false null true
+
+" Supported Functions for Date/Time types
+syn keyword sqlFunction	 ADD_DAYS ADD_MONTHS ADD_SECONDS ADD_YEARS COALESCE
+syn keyword sqlFunction	 CURRENT_DATE CURRENT_TIME CURRENT_TIMESTAMP CURRENT_UTCDATE
+syn keyword sqlFunction	 CURRENT_UTCTIME CURRENT_UTCTIMESTAMP
+syn keyword sqlFunction	 DAYNAME DAYOFMONTH DAYOFYEAR DAYS_BETWEEN EXTRACT
+syn keyword sqlFunction	 GREATEST HOUR IFNULL ISOWEEK LAST_DAY LEAST LOCALTOUTC
+syn keyword sqlFunction	 MINUTE MONTH MONTHNAME NEXT_DAY NOW QUARTER SECOND
+syn keyword sqlFunction	 SECONDS_BETWEEN UTCTOLOCAL WEEK WEEKDAY YEAR
+
+syn keyword sqlFunction	 TO_CHAR TO_DATE TO_DATS TO_NCHAR TO_TIME TO_TIMESTAMP UTCTOLOCAL
+
+" Aggregate
+syn keyword sqlFunction	 COUNT MIN MAX SUM AVG STDDEV VAR
+
+" Datatype conversion
+syn keyword sqlFunction	 CAST TO_ALPHANUM TO_BIGINT TO_BINARY TO_BLOB TO_CHAR TO_CLOB
+syn keyword sqlFunction	 TO_DATE TO_DATS TO_DECIMAL TO_DOUBLE TO_INT TO_INTEGER TO_NCHAR
+syn keyword sqlFunction	 TO_NCLOB TO_NVARCHAR TO_REAL TO_SECONDDATE TO_SMALLDECIMAL
+syn keyword sqlFunction	 TO_SMALLINT TO_TIME TO_TIMESTAMP TO_TINYINT TO_VARCHAR TO_VARBINARY
+
+" Number functions
+syn keyword sqlFunction	 ABS ACOS ASIN ATAN ATAN2 BINTOHEX BITAND CEIL COS COSH COT
+syn keyword sqlFunction	 EXP FLOOR GREATEST HEXTOBIN LEAST LN LOG MOD POWER ROUND
+syn keyword sqlFunction	 SIGN SIN SINH SQRT TAN TANH UMINUS
+
+" String functions
+syn keyword sqlFunction	 ASCII CHAR CONCAT LCASE LENGTH LOCATE LOWER LPAD LTRIM
+syn keyword sqlFunction	 NCHAR REPLACE RPAD RTRIM SUBSTR_AFTER SUBSTR_BEFORE
+syn keyword sqlFunction	 SUBSTRING TRIM UCASE UNICODE UPPER
+
+" Miscellaneous functions
+syn keyword sqlFunction	 COALESCE CURRENT_CONNECTION CURRENT_SCHEMA CURRENT_USER
+syn keyword sqlFunction	 GROUPING_ID IFNULL MAP NULLIF SESSION_CONTEXT SESSION_USER SYSUUIDSQL
+syn keyword sqlFunction	 GET_NUM_SERVERS
+
+
+" sp_ procedures
+" syn keyword sqlFunction  sp_addalias
+
+
+" Reserved keywords
+syn keyword sqlkeyword   ALL AS AT BEFORE
+syn keyword sqlkeyword   BEGIN BOTH BY
+syn keyword sqlkeyword   CONDITION
+syn keyword sqlkeyword   CURRVAL CURSOR DECLARE
+syn keyword sqlkeyword   DISTINCT DO ELSE ELSEIF ELSIF
+syn keyword sqlkeyword   END EXCEPTION EXEC
+syn keyword sqlkeyword   FOR FROM GROUP
+syn keyword sqlkeyword   HAVING IN
+syn keyword sqlkeyword   INOUT INTO IS
+syn keyword sqlkeyword   LEADING
+syn keyword sqlkeyword   LOOP MINUS NATURAL NEXTVAL
+syn keyword sqlkeyword   OF ON ORDER OUT
+syn keyword sqlkeyword   PRIOR RETURN RETURNS REVERSE
+syn keyword sqlkeyword   ROWID SELECT
+syn keyword sqlkeyword   SQL START STOP SYSDATE
+syn keyword sqlkeyword   SYSTIME SYSTIMESTAMP SYSUUID
+syn keyword sqlkeyword   TRAILING USING UTCDATE
+syn keyword sqlkeyword   UTCTIME UTCTIMESTAMP VALUES
+syn keyword sqlkeyword   WHILE
+syn keyword sqlkeyword   ANY SOME EXISTS ESCAPE
+
+" IF keywords
+syn keyword sqlkeyword	 IF
+
+" CASE keywords
+syn keyword sqlKeyword	 WHEN THEN
+
+" Syntax rules common to TEXT and SHORTTEXT keywords
+syn keyword sqlKeyword	 LANGUAGE DETECTION LINGUISTIC
+syn keyword sqlkeyword   MIME TYPE
+syn keyword sqlkeyword   EXACT WEIGHT FUZZY FUZZINESSTHRESHOLD SEARCH
+syn keyword sqlkeyword   PHRASE INDEX RATIO REBUILD
+syn keyword sqlkeyword   CONFIGURATION
+syn keyword sqlkeyword   SEARCH ONLY
+syn keyword sqlkeyword   FAST PREPROCESS
+syn keyword sqlkeyword   SYNC SYNCHRONOUS ASYNC ASYNCHRONOUS FLUSH QUEUE
+syn keyword sqlkeyword   EVERY AFTER MINUTES DOCUMENTS SUSPEND
+
+" Statement keywords (i.e. after ALTER or CREATE)
+syn keyword sqlkeyword   AUDIT POLICY
+syn keyword sqlkeyword   FULLTEXT
+syn keyword sqlkeyword   SEQUENCE RESTART
+syn keyword sqlkeyword   TABLE
+syn keyword sqlkeyword   PROCEDURE STATISTICS
+syn keyword sqlkeyword   SCHEMA
+syn keyword sqlkeyword   SYNONYM
+syn keyword sqlkeyword   VIEW
+syn keyword sqlkeyword   COLUMN
+syn keyword sqlkeyword   SYSTEM LICENSE
+syn keyword sqlkeyword   SESSION
+syn keyword sqlkeyword   CANCEL WORK
+syn keyword sqlkeyword   PLAN CACHE
+syn keyword sqlkeyword   LOGGING NOLOGGING RETENTION
+syn keyword sqlkeyword   RECONFIGURE SERVICE
+syn keyword sqlkeyword   RESET MONITORING
+syn keyword sqlkeyword   SAVE DURATION PERFTRACE FUNCTION_PROFILER
+syn keyword sqlkeyword   SAVEPOINT
+syn keyword sqlkeyword   USER
+syn keyword sqlkeyword   ROLE
+syn keyword sqlkeyword   ASC DESC
+syn keyword sqlkeyword   OWNED
+syn keyword sqlkeyword   DEPENDENCIES SCRAMBLE
+
+" Create sequence
+syn keyword sqlkeyword   INCREMENT MAXVALUE MINVALUE CYCLE
+
+" Create table
+syn keyword sqlkeyword   HISTORY GLOBAL LOCAL TEMPORARY
+
+" Create trigger
+syn keyword sqlkeyword   TRIGGER REFERENCING EACH DEFAULT
+syn keyword sqlkeyword   SIGNAL RESIGNAL MESSAGE_TEXT OLD NEW
+syn keyword sqlkeyword   EXIT HANDLER SQL_ERROR_CODE
+syn keyword sqlkeyword   TARGET CONDITION SIGNAL
+
+" Alter table
+syn keyword sqlkeyword   ADD DROP MODIFY GENERATED ALWAYS
+syn keyword sqlkeyword   UNIQUE BTREE CPBTREE PRIMARY KEY
+syn keyword sqlkeyword   CONSTRAINT PRELOAD NONE
+syn keyword sqlkeyword   ROW THREADS BATCH
+syn keyword sqlkeyword   MOVE PARTITION TO LOCATION PHYSICAL OTHERS
+syn keyword sqlkeyword   ROUNDROBIN PARTITIONS HASH RANGE VALUE
+syn keyword sqlkeyword   PERSISTENT DELTA AUTO AUTOMERGE
+
+" Create audit policy
+syn keyword sqlkeyword   AUDITING SUCCESSFUL UNSUCCESSFUL
+syn keyword sqlkeyword	 PRIVILEGE STRUCTURED CHANGE LEVEL
+syn keyword sqlkeyword	 EMERGENCY ALERT CRITICAL WARNING INFO
+
+" Privileges
+syn keyword sqlkeyword   DEBUG EXECUTE
+
+" Schema
+syn keyword sqlkeyword   CASCADE RESTRICT PARAMETERS SCAN
+
+" Traces
+syn keyword sqlkeyword   CLIENT CRASHDUMP EMERGENCYDUMP
+syn keyword sqlkeyword   INDEXSERVER NAMESERVER DAEMON
+syn keyword sqlkeyword   CLEAR REMOVE TRACES
+
+" Reclaim
+syn keyword sqlkeyword   RECLAIM DATA VOLUME VERSION SPACE DEFRAGMENT SPARSIFY
+
+" Join
+syn keyword sqlkeyword   INNER OUTER LEFT RIGHT FULL CROSS JOIN
+syn keyword sqlkeyword   GROUPING SETS ROLLUP CUBE
+syn keyword sqlkeyword   BEST LIMIT OFFSET
+syn keyword sqlkeyword   WITH SUBTOTAL BALANCE TOTAL
+syn keyword sqlkeyword   TEXT_FILTER FILL UP SORT MATCHES TOP
+syn keyword sqlkeyword   RESULT OVERVIEW PREFIX MULTIPLE RESULTSETS
+
+" Lock
+syn keyword sqlkeyword   EXCLUSIVE MODE NOWAIT
+
+" Transaction
+syn keyword sqlkeyword   TRANSACTION ISOLATION READ COMMITTED
+syn keyword sqlkeyword   REPEATABLE SERIALIZABLE WRITE
+
+" Saml
+syn keyword sqlkeyword   SAML ASSERTION PROVIDER SUBJECT ISSUER
+
+" User
+syn keyword sqlkeyword   PASSWORD IDENTIFIED EXTERNALLY ATTEMPTS ATTEMPTS
+syn keyword sqlkeyword	 ENABLE DISABLE OFF LIFETIME FORCE DEACTIVATE
+syn keyword sqlkeyword	 ACTIVATE IDENTITY KERBEROS
+
+" Grant
+syn keyword sqlkeyword   ADMIN BACKUP CATALOG SCENARIO INIFILE MONITOR
+syn keyword sqlkeyword   OPTIMIZER OPTION
+syn keyword sqlkeyword   RESOURCE STRUCTUREDPRIVILEGE TRACE
+
+" Import
+syn keyword sqlkeyword   CSV FILE CONTROL NO CHECK SKIP FIRST LIST
+syn keyword sqlkeyword	 RECORD DELIMITED FIELD OPTIONALLY ENCLOSED FORMAT
+
+" Roles
+syn keyword sqlkeyword   PUBLIC CONTENT_ADMIN MODELING MONITORING
+
+" Miscellaneous
+syn keyword sqlkeyword   APPLICATION BINARY IMMEDIATE COREFILE SECURITY DEFINER
+syn keyword sqlkeyword   DUMMY INVOKER MATERIALIZED MESSEGE_TEXT PARAMETER PARAMETERS
+syn keyword sqlkeyword   PART
+syn keyword sqlkeyword   CONSTANT SQLEXCEPTION SQLWARNING
+
+syn keyword sqlOperator  WHERE BETWEEN LIKE NULL CONTAINS
+syn keyword sqlOperator  AND OR NOT CASE
+syn keyword sqlOperator  UNION INTERSECT EXCEPT
+
+syn keyword sqlStatement ALTER CALL CALLS CREATE DROP RENAME TRUNCATE
+syn keyword sqlStatement DELETE INSERT UPDATE EXPLAIN
+syn keyword sqlStatement MERGE REPLACE UPSERT SELECT
+syn keyword sqlStatement SET UNSET LOAD UNLOAD
+syn keyword sqlStatement CONNECT DISCONNECT COMMIT LOCK ROLLBACK
+syn keyword sqlStatement GRANT REVOKE
+syn keyword sqlStatement EXPORT IMPORT
+
+
+syn keyword sqlType	 DATE TIME SECONDDATE TIMESTAMP TINYINT SMALLINT
+syn keyword sqlType	 INT INTEGER BIGINT SMALLDECIMAL DECIMAL
+syn keyword sqlType	 REAL DOUBLE FLOAT
+syn keyword sqlType	 VARCHAR NVARCHAR ALPHANUM SHORTTEXT VARBINARY
+syn keyword sqlType	 BLOB CLOB NCLOB TEXT DAYDATE
+
+syn keyword sqlOption    Webservice_namespace_host
+
+" Strings and characters:
+syn region sqlString		start=+"+    end=+"+ contains=@Spell
+syn region sqlString		start=+'+    end=+'+ contains=@Spell
+
+" Numbers:
+syn match sqlNumber		"-\=\<\d*\.\=[0-9_]\>"
+
+" Comments:
+syn region sqlDashComment	start=/--/ end=/$/ contains=@Spell
+syn region sqlSlashComment	start=/\/\// end=/$/ contains=@Spell
+syn region sqlMultiComment	start="/\*" end="\*/" contains=sqlMultiComment,@Spell
+syn cluster sqlComment	contains=sqlDashComment,sqlSlashComment,sqlMultiComment,@Spell
+syn sync ccomment sqlComment
+syn sync ccomment sqlDashComment
+syn sync ccomment sqlSlashComment
+
+hi def link sqlDashComment	Comment
+hi def link sqlSlashComment	Comment
+hi def link sqlMultiComment	Comment
+hi def link sqlNumber	        Number
+hi def link sqlOperator	        Operator
+hi def link sqlSpecial	        Special
+hi def link sqlKeyword	        Keyword
+hi def link sqlStatement	Statement
+hi def link sqlString	        String
+hi def link sqlType	        Type
+hi def link sqlFunction	        Function
+hi def link sqlOption	        PreProc
+
+let b:current_syntax = "sqlhana"
+
+" vim:sw=4:
diff --git a/runtime/syntax/tex.vim b/runtime/syntax/tex.vim
index 0eeff6f..d8a384a 100644
--- a/runtime/syntax/tex.vim
+++ b/runtime/syntax/tex.vim
@@ -1,8 +1,8 @@
 " Vim syntax file
 " Language:	TeX
-" Maintainer:	Dr. Charles E. Campbell, Jr. <NdrchipO@ScampbellPfamily.AbizM>
-" Last Change:	Apr 24, 2012
-" Version:	73
+" Maintainer:	Charles E. Campbell <NdrchipO@ScampbellPfamily.AbizM>
+" Last Change:	Nov 14, 2012
+" Version:	75
 " URL:		http://mysite.verizon.net/astronaut/vim/index.html#vimlinks_syntax
 "
 " Notes: {{{1
@@ -155,7 +155,7 @@
 " Try to flag {} and () mismatches: {{{1
 if !exists("g:tex_no_error")
  syn region texMatcher		matchgroup=Delimiter start="{" skip="\\\\\|\\[{}]"	end="}"		contains=@texMatchGroup,texError
- syn region texMatcher		matchgroup=Delimiter start="\["				end="]"		contains=@texMatchGroup,texError
+ syn region texMatcher		matchgroup=Delimiter start="\["				end="]"		contains=@texMatchGroup,texError,@NoSpell
 else
  syn region texMatcher		matchgroup=Delimiter start="{" skip="\\\\\|\\[{}]"	end="}"		contains=@texMatchGroup
  syn region texMatcher		matchgroup=Delimiter start="\["				end="]"		contains=@texMatchGroup
@@ -723,7 +723,7 @@
     \ ['leftarrowtail'	, '↢'],
     \ ['leftharpoondown', '↽'],
     \ ['leftharpoonup'	, '↼'],
-    \ ['leftrightarrow'	, '⇔'],
+    \ ['leftrightarrow'	, '↔'],
     \ ['Leftrightarrow'	, '⇔'],
     \ ['leftrightsquigarrow', '↭'],
     \ ['leftthreetimes'	, '⋋'],
diff --git a/runtime/syntax/vim.vim b/runtime/syntax/vim.vim
index f8e8465..391e650 100644
--- a/runtime/syntax/vim.vim
+++ b/runtime/syntax/vim.vim
@@ -1,8 +1,8 @@
 " Vim syntax file
 " Language:	Vim 7.3 script
-" Maintainer:	Dr. Charles E. Campbell, Jr. <NdrOchipS@PcampbellAfamily.Mbiz>
-" Last Change:	Jan 11, 2012
-" Version:	7.3-13
+" Maintainer:	Charles E. Campbell <NdrOchipS@PcampbellAfamily.Mbiz>
+" Last Change:	Nov 14, 2012
+" Version:	7.3-20
 " Automatically generated keyword lists: {{{1
 
 " Quit when a syntax file was already loaded {{{2
@@ -76,7 +76,7 @@
 " Function Names {{{2
 syn keyword vimFuncName contained	abs append argv atan2 bufexists bufname byte2line ceil cindent complete confirm cosh cursor did_filetype empty eventhandler exp extend filewritable findfile fmod foldclosed foldtext function getbufline getcharmod getcmdtype getfperm getftype getmatches getqflist gettabvar getwinposy globpath haslocaldir histdel hlexists iconv input inputrestore insert items len line localtime map match matchdelete matchstr min mode nextnonblank pathshorten prevnonblank pumvisible readfile reltimestr remote_foreground remote_read remove repeat reverse search searchpair searchpos serverlist setcmdpos setloclist setpos setreg settabwinvar shellescape sin sort spellbadword split str2float strchars strftime string strpart strtrans submatch synconcealed synIDattr synstack tabpagebuflist tabpagewinnr taglist tanh tolower tr type undotree virtcol winbufnr winheight winnr winrestview winwidth
 syn keyword vimFuncName contained	acos argc asin browse buflisted bufnr byteidx changenr clearmatches complete_add copy count deepcopy diff_filler escape executable expand feedkeys filter float2nr fnameescape foldclosedend foldtextresult garbagecollect getbufvar getcmdline getcwd getfsize getline getpid getreg gettabwinvar getwinvar has hasmapto histget hlID indent inputdialog inputsave isdirectory join libcall line2byte log maparg matchadd matchend max mkdir mzeval nr2char pow printf range reltime remote_expr remote_peek remote_send rename resolve round searchdecl searchpairpos server2client setbufvar setline setmatches setqflist settabvar setwinvar simplify sinh soundfold spellsuggest sqrt str2nr strdisplaywidth stridx strlen strridx strwidth substitute synID synIDtrans system tabpagenr tagfiles tan tempname toupper trunc undofile values visualmode wincol winline winrestcmd winsaveview writefile
-syn keyword vimFuncName contained	add argidx atan browsedir bufloaded bufwinnr call char2nr col complete_check cos cscope_connection delete diff_hlID eval exists expr8 filereadable finddir floor fnamemodify foldlevel foreground get getchar getcmdpos getfontname getftime getloclist getpos getregtype getwinposx glob has_key histadd histnr hostname index inputlist inputsecret islocked keys libcallnr lispindent log10 mapcheck matcharg matchlist pyeval py3eval luaeval
+syn keyword vimFuncName contained	add argidx atan browsedir bufloaded bufwinnr call char2nr col complete_check cos cscope_connection delete diff_hlID eval exists expr8 filereadable finddir floor fnamemodify foldlevel foreground get getchar getcmdpos getfontname getftime getloclist getpos getregtype getwinposx glob has_key histadd histnr hostname index inputlist inputsecret islocked keys libcallnr lispindent log10 mapcheck matcharg matchlist
 
 "--- syntax above generated by mkvimvim ---
 " Special Vim Highlighting (not automatic) {{{1
@@ -149,11 +149,12 @@
 
 " Operators: {{{2
 " =========
+" COMBAK: vimOperParen used to have "oneline"
 syn cluster	vimOperGroup	contains=vimFunc,vimFuncVar,vimOper,vimOperParen,vimNumber,vimString,vimRegister,vimContinue
 syn match	vimOper	"\(==\|!=\|>=\|<=\|=\~\|!\~\|>\|<\|=\)[?#]\{0,2}"	skipwhite nextgroup=vimString,vimSpecFile
 syn match	vimOper	"||\|&&\|[-+.]"	skipwhite nextgroup=vimString,vimSpecFile
-syn region	vimOperParen 	oneline matchgroup=vimParenSep	start="(" end=")" contains=@vimOperGroup
-syn region	vimOperParen	oneline matchgroup=vimSep	start="{" end="}" contains=@vimOperGroup nextgroup=vimVar,vimFuncVar
+syn region	vimOperParen 	matchgroup=vimParenSep	start="(" end=")" contains=@vimOperGroup
+syn region	vimOperParen	matchgroup=vimSep	start="{" end="}" contains=@vimOperGroup nextgroup=vimVar,vimFuncVar
 if !exists("g:vimsyn_noerror") && !exists("g:vimsyn_noopererror")
  syn match	vimOperError	")"
 endif
@@ -203,7 +204,7 @@
 endif
 syn case ignore
 syn keyword	vimUserAttrbKey   contained	bar	ban[g]	cou[nt]	ra[nge] com[plete]	n[args]	re[gister]
-syn keyword	vimUserAttrbCmplt contained	augroup buffer command dir environment event expression file function help highlight mapping menu option shellcmd something tag tag_listfiles var
+syn keyword	vimUserAttrbCmplt contained	augroup buffer color command compiler cscope dir environment event expression file file_in_path filetype function help highlight locale mapping menu option shellcmd sign syntax tag tag_listfiles var
 syn keyword	vimUserAttrbCmplt contained	custom customlist nextgroup=vimUserAttrbCmpltFunc,vimUserCmdError
 syn match	vimUserAttrbCmpltFunc contained	",\%([sS]:\|<[sS][iI][dD]>\)\=\%(\h\w*\%(#\u\w*\)\+\|\u\w*\)"hs=s+1 nextgroup=vimUserCmdError
 
@@ -328,7 +329,7 @@
 syn match	vimMapBang	contained	"!"			skipwhite nextgroup=vimMapMod,vimMapLhs
 syn match	vimMapMod	contained	"\c<\(buffer\|expr\|\(local\)\=leader\|plug\|script\|sid\|unique\|silent\)\+>" contains=vimMapModKey,vimMapModErr skipwhite nextgroup=vimMapMod,vimMapLhs
 syn match	vimMapRhs	contained	".*" contains=vimNotation,vimCtrlChar	skipnl nextgroup=vimMapRhsExtend
-syn match	vimMapRhsExtend	contained	"^\s*\\.*$"			contains=vimContinue
+syn match	vimMapRhsExtend	contained	"^\s*\\.*$"			contains=vimNotation,vimCtrlChar,vimContinue	skipnl nextgroup=vimMapRhsExtend
 syn case ignore
 syn keyword	vimMapModKey	contained	buffer	expr	leader	localleader	plug	script	sid	silent	unique
 syn case match
@@ -360,8 +361,8 @@
 " User Function Highlighting {{{2
 " (following Gautam Iyer's suggestion)
 " ==========================
-syn match vimFunc		"\%(\%([sSgGbBwWtTlL]:\|<[sS][iI][dD]>\)\=\%([a-zA-Z0-9_.]\+\.\)*\I[a-zA-Z0-9_.]*\)\ze\s*("		contains=vimFuncName,vimUserFunc,vimExecute
-syn match vimUserFunc contained	"\%(\%([sSgGbBwWtTlL]:\|<[sS][iI][dD]>\)\=\%([a-zA-Z0-9_.]\+\.\)*\I[a-zA-Z0-9_.]*\)\|\<\u[a-zA-Z0-9.]*\>\|\<if\>"	contains=vimNotation
+syn match vimFunc		"\%(\%([sSgGbBwWtTlL]:\|<[sS][iI][dD]>\)\=\%([a-zA-Z0-9_]\+\.\)*\I[a-zA-Z0-9_.]*\)\ze\s*("		contains=vimFuncName,vimUserFunc,vimExecute
+syn match vimUserFunc contained	"\%(\%([sSgGbBwWtTlL]:\|<[sS][iI][dD]>\)\=\%([a-zA-Z0-9_]\+\.\)*\I[a-zA-Z0-9_.]*\)\|\<\u[a-zA-Z0-9.]*\>\|\<if\>"	contains=vimNotation
 syn match vimNotFunc	"\<if\>\|\<el\%[seif]\>\|\<return\>\|\<while\>"
 
 " Errors And Warnings: {{{2
@@ -429,7 +430,7 @@
 syn region	vimSynMatchRegion	contained keepend	matchgroup=vimGroupName start="\k\+" matchgroup=vimSep end="|\|$" contains=@vimSynMtchGroup
 syn match	vimSynMtchOpt	contained	"\<\(conceal\|transparent\|contained\|excludenl\|skipempty\|skipwhite\|display\|extend\|skipnl\|fold\)\>"
 if has("conceal")
- syn match	vimSynMtchOpt	contained	"\<cchar="	nextgroup=VimSynMtchCchar
+ syn match	vimSynMtchOpt	contained	"\<cchar="	nextgroup=vimSynMtchCchar
  syn match	vimSynMtchCchar	contained	"\S"
 endif
 syn cluster vimFuncBodyList add=vimSynMtchGroup
@@ -510,17 +511,18 @@
 syn match	vimHiTerm	contained	"\cterm="he=e-1		nextgroup=vimHiAttribList
 syn match	vimHiStartStop	contained	"\c\(start\|stop\)="he=e-1	nextgroup=vimHiTermcap,vimOption
 syn match	vimHiCTerm	contained	"\ccterm="he=e-1		nextgroup=vimHiAttribList
-syn match	vimHiCtermFgBg	contained	"\ccterm[fb]g="he=e-1	nextgroup=vimNumber,vimHiCtermColor,vimFgBgAttrib,vimHiCtermError
+syn match	vimHiCtermFgBg	contained	"\ccterm[fb]g="he=e-1	nextgroup=vimHiNmbr,vimHiCtermColor,vimFgBgAttrib,vimHiCtermError
 syn match	vimHiGui	contained	"\cgui="he=e-1		nextgroup=vimHiAttribList
 syn match	vimHiGuiFont	contained	"\cfont="he=e-1		nextgroup=vimHiFontname
 syn match	vimHiGuiFgBg	contained	"\cgui\%([fb]g\|sp\)="he=e-1	nextgroup=vimHiGroup,vimHiGuiFontname,vimHiGuiRgb,vimFgBgAttrib
 syn match	vimHiTermcap	contained	"\S\+"		contains=vimNotation
+syn match	vimHiNmbr	contained	'\d\+'
 
 " Highlight: clear {{{2
 syn keyword	vimHiClear	contained	clear	nextgroup=vimHiGroup
 
 " Highlight: link {{{2
-syn region	vimHiLink	contained oneline matchgroup=vimCommand start="\<\(def\%[ault]\s\+\)\=link\>\|\<def\>" end="$"	contains=vimHiGroup,vimGroup,vimHLGroup,vimNotation
+syn region	vimHiLink	contained oneline matchgroup=vimCommand start="\(\<hi\%[ghlight]\s\+\)\@<=\(\(def\%[ault]\s\+\)\=link\>\|\<def\>\)" end="$"	contains=vimHiGroup,vimGroup,vimHLGroup,vimNotation
 syn cluster vimFuncBodyList add=vimHiLink
 
 " Control Characters {{{2
@@ -562,7 +564,12 @@
 " [-- lua --] {{{3
 let s:luapath= fnameescape(expand("<sfile>:p:h")."/lua.vim")
 if !filereadable(s:luapath)
- let s:luapath= fnameescape(globpath(&rtp,"syntax/lua.vim"))
+ for s:luapath in split(globpath(&rtp,"syntax/lua.vim"),"\n")
+  if filereadable(fnameescape(s:luapath))
+   let s:luapath= fnameescape(s:luapath)
+   break
+  endif
+ endfor
 endif
 if (g:vimsyn_embed =~ 'l' && has("lua")) && filereadable(s:luapath)
  unlet! b:current_syntax
@@ -584,7 +591,12 @@
 " [-- perl --] {{{3
 let s:perlpath= fnameescape(expand("<sfile>:p:h")."/perl.vim")
 if !filereadable(s:perlpath)
- let s:perlpath= fnameescape(globpath(&rtp,"syntax/perl.vim"))
+ for s:perlpath in split(globpath(&rtp,"syntax/perl.vim"),"\n")
+  if filereadable(fnameescape(s:perlpath))
+   let s:perlpath= fnameescape(s:perlpath)
+   break
+  endif
+ endfor
 endif
 if (g:vimsyn_embed =~ 'p' && has("perl")) && filereadable(s:perlpath)
  unlet! b:current_syntax
@@ -606,7 +618,12 @@
 " [-- ruby --] {{{3
 let s:rubypath= fnameescape(expand("<sfile>:p:h")."/ruby.vim")
 if !filereadable(s:rubypath)
- let s:rubypath= fnameescape(globpath(&rtp,"syntax/ruby.vim"))
+ for s:rubypath in split(globpath(&rtp,"syntax/ruby.vim"),"\n")
+  if filereadable(fnameescape(s:rubypath))
+   let s:rubypath= fnameescape(s:rubypath)
+   break
+  endif
+ endfor
 endif
 if (g:vimsyn_embed =~ 'r' && has("ruby")) && filereadable(s:rubypath)
  unlet! b:current_syntax
@@ -627,9 +644,14 @@
 " [-- python --] {{{3
 let s:pythonpath= fnameescape(expand("<sfile>:p:h")."/python.vim")
 if !filereadable(s:pythonpath)
- let s:pythonpath= fnameescape(globpath(&rtp,"syntax/python.vim"))
+ for s:pythonpath in split(globpath(&rtp,"syntax/python.vim"),"\n")
+  if filereadable(fnameescape(s:pythonpath))
+   let s:pythonpath= fnameescape(s:pythonpath)
+   break
+  endif
+ endfor
 endif
-if (g:vimsyn_embed =~ 'P' && has("python")) && filereadable(s:pythonpath)
+if g:vimsyn_embed =~ 'P' && (has("python") || has("python3")) && filereadable(s:pythonpath)
  unlet! b:current_syntax
  exe "syn include @vimPythonScript ".s:pythonpath
  if exists("g:vimsyn_folding") && g:vimsyn_folding =~ 'P'
@@ -656,7 +678,12 @@
 if s:trytcl
  let s:tclpath= fnameescape(expand("<sfile>:p:h")."/tcl.vim")
  if !filereadable(s:tclpath)
-  let s:tclpath= fnameescape(globpath(&rtp,"syntax/tcl.vim"))
+  for s:tclpath in split(globpath(&rtp,"syntax/tcl.vim"),"\n")
+   if filereadable(fnameescape(s:tclpath))
+    let s:tclpath= fnameescape(s:tclpath)
+    break
+   endif
+  endfor
  endif
  if (g:vimsyn_embed =~ 't' && has("tcl")) && filereadable(s:tclpath)
   unlet! b:current_syntax
@@ -683,7 +710,12 @@
 " [-- mzscheme --] {{{3
 let s:mzschemepath= fnameescape(expand("<sfile>:p:h")."/scheme.vim")
 if !filereadable(s:mzschemepath)
- let s:mzschemepath= fnameescape(globpath(&rtp,"syntax/scheme.vim"))
+ for s:mzschemepath in split(globpath(&rtp,"syntax/mzscheme.vim"),"\n")
+  if filereadable(fnameescape(s:mzschemepath))
+   let s:mzschemepath= fnameescape(s:mzschemepath)
+   break
+  endif
+ endfor
 endif
 if (g:vimsyn_embed =~ 'm' && has("mzscheme")) && filereadable(s:mzschemepath)
  unlet! b:current_syntax
@@ -879,6 +911,7 @@
 hi def link vimUserFunc	Normal
 hi def link vimVar	Identifier
 hi def link vimWarn	WarningMsg
+hi def link vimHiNmbr	Number
 
 " Current Syntax Variable: {{{2
 let b:current_syntax = "vim"
diff --git a/runtime/syntax/yacc.vim b/runtime/syntax/yacc.vim
index 4ddf078..3da7ffc 100644
--- a/runtime/syntax/yacc.vim
+++ b/runtime/syntax/yacc.vim
@@ -1,8 +1,8 @@
 " Vim syntax file
 " Language:	Yacc
-" Maintainer:	Charles E. Campbell, Jr. <NdrOchipS@PcampbellAfamily.Mbiz>
-" Last Change:	Aug 12, 2010
-" Version:	9
+" Maintainer:	Charles E. Campbell <NdrOchipS@PcampbellAfamily.Mbiz>
+" Last Change:	Nov 14, 2012
+" Version:	10
 " URL:	http://mysite.verizon.net/astronaut/vim/index.html#vimlinks_syntax
 "
 " Options: {{{1
@@ -20,18 +20,24 @@
 " ---------------------------------------------------------------------
 "  Folding Support {{{1
 if has("folding")
- com! -nargs=+ HiFold	<args> fold
+ com! -nargs=+ SynFold	<args> fold
 else
- com! -nargs=+ HiFold	<args>
+ com! -nargs=+ SynFold	<args>
 endif
 
 " ---------------------------------------------------------------------
 " Read the C syntax to start with {{{1
-if exists("g:yacc_uses_cpp")
- syn include @yaccCode	<sfile>:p:h/cpp.vim
-else
- syn include @yaccCode	<sfile>:p:h/c.vim
+" Read the C/C++ syntax to start with
+let s:Cpath= fnameescape(expand("<sfile>:p:h").(exists("g:yacc_uses_cpp")? "/cpp.vim" : "/c.vim"))
+if !filereadable(s:Cpath)
+ for s:Cpath in split(globpath(&rtp,(exists("g:yacc_uses_cpp")? "syntax/cpp.vim" : "syntax/c.vim")),"\n")
+  if filereadable(fnameescape(s:Cpath))
+   let s:Cpath= fnameescape(s:Cpath)
+   break
+  endif
+ endfor
 endif
+exe "syn include @yaccCode ".s:Cpath
 
 " ---------------------------------------------------------------------
 "  Yacc Clusters: {{{1
@@ -40,12 +46,12 @@
 
 " ---------------------------------------------------------------------
 "  Yacc Sections: {{{1
-HiFold syn	region	yaccInit	start='.'ms=s-1,rs=s-1	matchgroup=yaccSectionSep	end='^%%$'me=e-2,re=e-2	contains=@yaccInitCluster	nextgroup=yaccRules	skipwhite skipempty contained
-HiFold syn	region	yaccInit2      start='\%^.'ms=s-1,rs=s-1	matchgroup=yaccSectionSep	end='^%%$'me=e-2,re=e-2	contains=@yaccInitCluster	nextgroup=yaccRules	skipwhite skipempty
-HiFold syn	region	yaccHeader2	matchgroup=yaccSep	start="^\s*\zs%{"	end="^\s*%}"		contains=@yaccCode	nextgroup=yaccInit	skipwhite skipempty contained
-HiFold syn	region	yaccHeader	matchgroup=yaccSep	start="^\s*\zs%{"	end="^\s*%}"		contains=@yaccCode	nextgroup=yaccInit	skipwhite skipempty
-HiFold syn	region	yaccRules	matchgroup=yaccSectionSep	start='^%%$'		end='^%%$'me=e-2,re=e-2	contains=@yaccRulesCluster	nextgroup=yaccEndCode	skipwhite skipempty contained
-HiFold syn	region	yaccEndCode	matchgroup=yaccSectionSep	start='^%%$'		end='\%$'		contains=@yaccCode	contained
+SynFold syn	region	yaccInit	start='.'ms=s-1,rs=s-1	matchgroup=yaccSectionSep	end='^%%$'me=e-2,re=e-2	contains=@yaccInitCluster	nextgroup=yaccRules	skipwhite skipempty contained
+SynFold syn	region	yaccInit2      start='\%^.'ms=s-1,rs=s-1	matchgroup=yaccSectionSep	end='^%%$'me=e-2,re=e-2	contains=@yaccInitCluster	nextgroup=yaccRules	skipwhite skipempty
+SynFold syn	region	yaccHeader2	matchgroup=yaccSep	start="^\s*\zs%{"	end="^\s*%}"		contains=@yaccCode	nextgroup=yaccInit	skipwhite skipempty contained
+SynFold syn	region	yaccHeader	matchgroup=yaccSep	start="^\s*\zs%{"	end="^\s*%}"		contains=@yaccCode	nextgroup=yaccInit	skipwhite skipempty
+SynFold syn	region	yaccRules	matchgroup=yaccSectionSep	start='^%%$'		end='^%%$'me=e-2,re=e-2	contains=@yaccRulesCluster	nextgroup=yaccEndCode	skipwhite skipempty contained
+SynFold syn	region	yaccEndCode	matchgroup=yaccSectionSep	start='^%%$'		end='\%$'		contains=@yaccCode	contained
 
 " ---------------------------------------------------------------------
 " Yacc Commands: {{{1
@@ -63,11 +69,11 @@
 syn	keyword	yaccKeyActn	yyerrok yyclearin	contained
 
 syn	match	yaccUnionStart	"^%union"	skipwhite skipnl nextgroup=yaccUnion	contained
-HiFold syn	region	yaccUnion	matchgroup=yaccCurly start="{" matchgroup=yaccCurly end="}" contains=@yaccCode	contained
+SynFold syn	region	yaccUnion	matchgroup=yaccCurly start="{" matchgroup=yaccCurly end="}" contains=@yaccCode	contained
 syn	match	yaccBrkt	"[<>]"	contained
 syn	match	yaccType	"<[a-zA-Z_][a-zA-Z0-9_]*>"	contains=yaccBrkt	contained
 
-HiFold syn	region	yaccNonterminal	start="^\s*\a\w*\ze\_s*\(/\*\_.\{-}\*/\)\=\_s*:"	matchgroup=yaccDelim end=";"	matchgroup=yaccSectionSep end='^%%$'me=e-2,re=e-2 contains=yaccAction,yaccDelim,yaccString,yaccComment	contained
+SynFold syn	region	yaccNonterminal	start="^\s*\a\w*\ze\_s*\(/\*\_.\{-}\*/\)\=\_s*:"	matchgroup=yaccDelim end=";"	matchgroup=yaccSectionSep end='^%%$'me=e-2,re=e-2 contains=yaccAction,yaccDelim,yaccString,yaccComment	contained
 syn	region	yaccComment	start="/\*"	end="\*/"
 syn	match	yaccString	"'[^']*'"	contained
 
@@ -75,7 +81,8 @@
 " ---------------------------------------------------------------------
 " I'd really like to highlight just the outer {}.  Any suggestions??? {{{1
 syn	match	yaccCurlyError	"[{}]"
-HiFold syn	region	yaccAction	matchgroup=yaccCurly start="{" end="}" contains=@yaccCode	contained
+SynFold syn	region	yaccAction	matchgroup=yaccCurly start="{" end="}" 	contains=@yaccCode,yaccVar		contained
+syn	match	yaccVar	'\$\d\+\|\$\$\|\$<\I\i*>\$\|\$<\I\i*>\d\+'	containedin=cParen,cPreProc,cMulti	contained
 
 " ---------------------------------------------------------------------
 " Yacc synchronization: {{{1
@@ -84,39 +91,30 @@
 " ---------------------------------------------------------------------
 " Define the default highlighting. {{{1
 if !exists("did_yacc_syn_inits")
-  command -nargs=+ HiLink hi def link <args>
-
-  " Internal yacc highlighting links {{{2
-  HiLink yaccBrkt	yaccStmt
-  HiLink yaccKey	yaccStmt
-  HiLink yaccOper	yaccStmt
-  HiLink yaccUnionStart	yaccKey
-
-  " External yacc highlighting links {{{2
-  HiLink yaccComment	Comment
-  HiLink yaccCurly	Delimiter
-  HiLink yaccCurlyError	Error
-  HiLink yaccDefines	cDefine
-  HiLink yaccParseParam	yaccParseOption
-  HiLink yaccParseOption	cDefine
-  HiLink yaccNonterminal	Function
-  HiLink yaccDelim	Delimiter
-  HiLink yaccKeyActn	Special
-  HiLink yaccSectionSep	Todo
-  HiLink yaccSep	Delimiter
-  HiLink yaccString	String
-  HiLink yaccStmt	Statement
-  HiLink yaccType	Type
-
-  " since Bram doesn't like my Delimiter :| {{{2
-  HiLink Delimiter	Type
-
-  delcommand HiLink
+  hi def link yaccBrkt	yaccStmt
+  hi def link yaccComment	Comment
+  hi def link yaccCurly	Delimiter
+  hi def link yaccCurlyError	Error
+  hi def link yaccDefines	cDefine
+  hi def link yaccDelim	Delimiter
+  hi def link yaccKeyActn	Special
+  hi def link yaccKey	yaccStmt
+  hi def link yaccNonterminal	Function
+  hi def link yaccOper	yaccStmt
+  hi def link yaccParseOption	cDefine
+  hi def link yaccParseParam	yaccParseOption
+  hi def link yaccSectionSep	Todo
+  hi def link yaccSep	Delimiter
+  hi def link yaccStmt	Statement
+  hi def link yaccString	String
+  hi def link yaccType	Type
+  hi def link yaccUnionStart	yaccKey
+  hi def link yaccVar	Special
 endif
 
 " ---------------------------------------------------------------------
 "  Cleanup: {{{1
-delcommand HiFold
+delcommand SynFold
 let b:current_syntax = "yacc"
 
 " ---------------------------------------------------------------------