Update runtime files.
This commit is contained in:
@ -1,10 +1,23 @@
|
||||
" Vim syntax file
|
||||
" Language: COBOL
|
||||
" Maintainer: Tim Pope <vimNOSPAM@tpope.org>
|
||||
" Maintainer: Ankit Jain <ajatkj@yahoo.co.in>
|
||||
" (formerly Tim Pope <vimNOSPAM@tpope.info>)
|
||||
" (formerly Davyd Ondrejko <vondraco@columbus.rr.com>)
|
||||
" (formerly Sitaram Chamarty <sitaram@diac.com> and
|
||||
" James Mitchell <james_mitchell@acm.org>)
|
||||
" Last Change: 2015 Feb 13
|
||||
" Last Change: 2019 Mar 22
|
||||
" Ankit Jain 22.03.2019 Changes & fixes:
|
||||
" 1. Include inline comments
|
||||
" 2. Use comment highlight for bad lines
|
||||
" 3. Change certain 'keywords' to 'matches'
|
||||
" for additional highlighting
|
||||
" 4. Different highlighting for COPY, GO TO &
|
||||
" CALL lines
|
||||
" 5. Fix for COMP keyword
|
||||
" 6. Fix for PROCEDURE DIVISION highlighting
|
||||
" 7. Highlight EXIT PROGRAM like STOP RUN
|
||||
" 8. Highlight X & A in PIC clause
|
||||
" Tag: #C22032019
|
||||
|
||||
" quit when a syntax file was already loaded
|
||||
if exists("b:current_syntax")
|
||||
@ -12,7 +25,11 @@ if exists("b:current_syntax")
|
||||
endif
|
||||
|
||||
" MOST important - else most of the keywords wont work!
|
||||
setlocal isk=@,48-57,-
|
||||
setlocal isk=@,48-57,-,_
|
||||
|
||||
if !exists('g:cobol_inline_comment')
|
||||
let g:cobol_inline_comment=0
|
||||
endif
|
||||
|
||||
syn case ignore
|
||||
|
||||
@ -29,7 +46,10 @@ syn match cobolComment "[/*C].*$" contained
|
||||
syn match cobolCompiler "$.*$" contained
|
||||
syn match cobolLine ".*$" contained contains=cobolReserved,@cobolLine
|
||||
|
||||
syn match cobolDivision "[A-Z][A-Z0-9-]*[A-Z0-9]\s\+DIVISION\."he=e-1 contained contains=cobolDivisionName
|
||||
"#C22032019: Fix for PROCEDURE DIVISION USING highlighting, removed . from the
|
||||
"end of the regex
|
||||
"syn match cobolDivision \"[A-Z][A-Z0-9-]*[A-Z0-9]\s\+DIVISION\."he=e-1 contained contains=cobolDivisionName
|
||||
syn match cobolDivision "[A-Z][A-Z0-9-]*[A-Z0-9]\s\+DIVISION" contained contains=cobolDivisionName
|
||||
syn keyword cobolDivisionName contained IDENTIFICATION ENVIRONMENT DATA PROCEDURE
|
||||
syn match cobolSection "[A-Z][A-Z0-9-]*[A-Z0-9]\s\+SECTION\."he=e-1 contained contains=cobolSectionName
|
||||
syn keyword cobolSectionName contained CONFIGURATION INPUT-OUTPUT FILE WORKING-STORAGE LOCAL-STORAGE LINKAGE
|
||||
@ -38,10 +58,12 @@ syn keyword cobolParagraphName contained PROGRAM-ID SOURCE-COMPUTER OBJECT-COMP
|
||||
|
||||
|
||||
"syn match cobolKeys "^\a\{1,6\}" contains=cobolReserved
|
||||
"#C22032019: Remove BY, REPLACING, PROGRAM, TO, IN from 'keyword' group and add
|
||||
"to 'match' group or other 'keyword' group
|
||||
syn keyword cobolReserved contained ACCEPT ACCESS ADD ADDRESS ADVANCING AFTER ALPHABET ALPHABETIC
|
||||
syn keyword cobolReserved contained ALPHABETIC-LOWER ALPHABETIC-UPPER ALPHANUMERIC ALPHANUMERIC-EDITED ALS
|
||||
syn keyword cobolReserved contained ALTERNATE AND ANY ARE AREA AREAS ASCENDING ASSIGN AT AUTHOR BEFORE BINARY
|
||||
syn keyword cobolReserved contained BLANK BLOCK BOTTOM BY CANCEL CBLL CD CF CH CHARACTER CHARACTERS CLASS
|
||||
syn keyword cobolReserved contained BLANK BLOCK BOTTOM CANCEL CBLL CD CF CH CHARACTER CHARACTERS CLASS
|
||||
syn keyword cobolReserved contained CLOCK-UNITS CLOSE COBOL CODE CODE-SET COLLATING COLUMN COMMA COMMON
|
||||
syn keyword cobolReserved contained COMMUNICATIONS COMPUTATIONAL COMPUTE CONTENT CONTINUE
|
||||
syn keyword cobolReserved contained CONTROL CONVERTING CORR CORRESPONDING COUNT CURRENCY DATE DATE-COMPILED
|
||||
@ -55,52 +77,79 @@ syn keyword cobolReserved contained END-REWRITE END-SEARCH END-START END-STRING
|
||||
syn keyword cobolReserved contained END-WRITE EQUAL ERROR ESI EVALUATE EVERY EXCEPTION EXIT
|
||||
syn keyword cobolReserved contained EXTEND EXTERNAL FALSE FD FILLER FINAL FIRST FOOTING FOR FROM
|
||||
syn keyword cobolReserved contained GENERATE GIVING GLOBAL GREATER GROUP HEADING HIGH-VALUE HIGH-VALUES I-O
|
||||
syn keyword cobolReserved contained IN INDEX INDEXED INDICATE INITIAL INITIALIZE
|
||||
syn keyword cobolReserved contained INDEX INDEXED INDICATE INITIAL INITIALIZE
|
||||
syn keyword cobolReserved contained INITIATE INPUT INSPECT INSTALLATION INTO IS JUST
|
||||
syn keyword cobolReserved contained JUSTIFIED KEY LABEL LAST LEADING LEFT LENGTH LOCK MEMORY
|
||||
syn keyword cobolReserved contained MERGE MESSAGE MODE MODULES MOVE MULTIPLE MULTIPLY NATIVE NEGATIVE NEXT NO NOT
|
||||
syn keyword cobolReserved contained NUMBER NUMERIC NUMERIC-EDITED OCCURS OF OFF OMITTED ON OPEN
|
||||
syn keyword cobolReserved contained OPTIONAL OR ORDER ORGANIZATION OTHER OUTPUT OVERFLOW PACKED-DECIMAL PADDING
|
||||
syn keyword cobolReserved contained PAGE PAGE-COUNTER PERFORM PF PH PIC PICTURE PLUS POINTER POSITION POSITIVE
|
||||
syn keyword cobolReserved contained PRINTING PROCEDURES PROCEDD PROGRAM PURGE QUEUE QUOTES
|
||||
syn keyword cobolReserved contained PRINTING PROCEDURES PROCEDD PURGE QUEUE QUOTES
|
||||
syn keyword cobolReserved contained RANDOM RD READ RECEIVE RECORD RECORDS REDEFINES REEL REFERENCE REFERENCES
|
||||
syn keyword cobolReserved contained RELATIVE RELEASE REMAINDER REMOVAL REPLACE REPLACING REPORT REPORTING
|
||||
syn keyword cobolReserved contained RELATIVE RELEASE REMAINDER REMOVAL REPLACE REPORT REPORTING
|
||||
syn keyword cobolReserved contained REPORTS RERUN RESERVE RESET RETURN RETURNING REVERSED REWIND REWRITE RF RH
|
||||
syn keyword cobolReserved contained RIGHT ROUNDED RUN SAME SD SEARCH SECTION SECURITY SEGMENT SEGMENT-LIMITED
|
||||
syn keyword cobolReserved contained SELECT SEND SENTENCE SEPARATE SEQUENCE SEQUENTIAL SET SIGN SIZE SORT
|
||||
syn keyword cobolReserved contained SORT-MERGE SOURCE STANDARD
|
||||
syn keyword cobolReserved contained STANDARD-1 STANDARD-2 START STATUS STOP STRING SUB-QUEUE-1 SUB-QUEUE-2
|
||||
syn keyword cobolReserved contained SUB-QUEUE-3 SUBTRACT SUM SUPPRESS SYMBOLIC SYNC SYNCHRONIZED TABLE TALLYING
|
||||
syn keyword cobolReserved contained TAPE TERMINAL TERMINATE TEST TEXT THAN THEN THROUGH THRU TIME TIMES TO TOP
|
||||
syn keyword cobolReserved contained TAPE TERMINAL TERMINATE TEST TEXT THAN THEN THROUGH THRU TIME TIMES TOP
|
||||
syn keyword cobolReserved contained TRAILING TRUE TYPE UNIT UNSTRING UNTIL UP UPON USAGE USE USING VALUE VALUES
|
||||
syn keyword cobolReserved contained VARYING WHEN WITH WORDS WRITE
|
||||
syn match cobolReserved contained "\<CONTAINS\>"
|
||||
syn match cobolReserved contained "\<\(IF\|INVALID\|END\|EOP\)\>"
|
||||
syn match cobolReserved contained "\<ALL\>"
|
||||
" #C22032019: Add BY as match instead of keyword: BY not followed by ==
|
||||
syn match cobolReserved contained "\<BY\>\s\+\(==\)\@!"
|
||||
syn match cobolReserved contained "\<TO\>"
|
||||
|
||||
syn cluster cobolLine add=cobolConstant,cobolNumber,cobolPic
|
||||
syn keyword cobolConstant SPACE SPACES NULL ZERO ZEROES ZEROS LOW-VALUE LOW-VALUES
|
||||
|
||||
" #C22032019: Fix for many pic clauses
|
||||
syn match cobolNumber "\<-\=\d*\.\=\d\+\>" contained
|
||||
syn match cobolPic "\<S*9\+\>" contained
|
||||
" syn match cobolPic \"\<S*9\+\>" contained
|
||||
syn match cobolPic "\<S*9\+V*9*\>" contained
|
||||
syn match cobolPic "\<$*\.\=9\+\>" contained
|
||||
syn match cobolPic "\<Z*\.\=9\+\>" contained
|
||||
syn match cobolPic "\<V9\+\>" contained
|
||||
syn match cobolPic "\<9\+V\>" contained
|
||||
syn match cobolPic "\<-\+[Z9]\+\>" contained
|
||||
syn match cobolTodo "todo" contained containedin=cobolComment
|
||||
" syn match cobolPic \"\<-\+[Z9]\+\>" contained
|
||||
syn match cobolPic "\<-*[Z9]\+-*\>" contained
|
||||
" #C22032019: Add Z,X and A to cobolPic
|
||||
syn match cobolPic "\<[ZXA]\+\>" contained
|
||||
syn match cobolTodo "todo" contained containedin=cobolInlineComment,cobolComment
|
||||
|
||||
" For MicroFocus or other inline comments, include this line.
|
||||
" syn region cobolComment start="*>" end="$" contains=cobolTodo,cobolMarker
|
||||
if g:cobol_inline_comment == 1
|
||||
syn region cobolInlineComment start="*>" end="$" contains=cobolTodo,cobolMarker
|
||||
syn cluster cobolLine add=cobolInlineComment
|
||||
endif
|
||||
|
||||
syn match cobolBadLine "[^ D\*$/-].*" contained
|
||||
|
||||
" If comment mark somehow gets into column past Column 7.
|
||||
syn match cobolBadLine "\s\+\*.*" contained
|
||||
if g:cobol_inline_comment == 1
|
||||
" #C22032019: It is a bad line only if * is not followed by > when inline
|
||||
" comments enabled
|
||||
syn match cobolBadLine "\s\+\*\(>\)\@!.*" contained
|
||||
else
|
||||
syn match cobolBadLine "\s\+\*.*" contained
|
||||
endif
|
||||
syn cluster cobolStart add=cobolBadLine
|
||||
|
||||
|
||||
syn keyword cobolGoTo GO GOTO
|
||||
syn keyword cobolCopy COPY
|
||||
" #C22032019: Different highlighting for GO TO statements
|
||||
" syn keyword cobolGoTo GO GOTO
|
||||
syn keyword cobolGoTo GOTO
|
||||
syn match cobolGoTo /\<GO\>\s\+\<TO\>/
|
||||
syn match cobolGoToPara /\<GO\>\s\+\<TO\>\s\+[A-Z0-9-]\+/ contains=cobolGoTo
|
||||
" #C22032019: Highlight copybook name and location in using different group
|
||||
" syn keyword cobolCopy COPY
|
||||
syn match cobolCopy "\<COPY\>\|\<IN\>"
|
||||
syn match cobolCopy "\<REPLACING\>\s\+\(==\)\@="
|
||||
syn match cobolCopy "\<BY\>\s\+\(==\)\@="
|
||||
syn match cobolCopyName "\<COPY\>\s\+[A-Z0-9]\+\(\s\+\<IN\>\s\+[A-Z0-9]\+\)\?" contains=cobolCopy
|
||||
syn cluster cobolLine add=cobolGoToPara,cobolCopyName
|
||||
|
||||
" cobolBAD: things that are BAD NEWS!
|
||||
syn keyword cobolBAD ALTER ENTER RENAMES
|
||||
@ -109,8 +158,14 @@ syn cluster cobolLine add=cobolGoTo,cobolCopy,cobolBAD,cobolWatch,cobolEXE
|
||||
|
||||
" cobolWatch: things that are important when trying to understand a program
|
||||
syn keyword cobolWatch OCCURS DEPENDING VARYING BINARY COMP REDEFINES
|
||||
syn keyword cobolWatch REPLACING RUN
|
||||
syn match cobolWatch "COMP-[123456XN]"
|
||||
" #C22032019: Remove REPLACING from cobolWatch 'keyword' group and add to cobolCopy &
|
||||
" cobolWatch 'match' group
|
||||
" syn keyword cobolWatch REPLACING RUN
|
||||
syn keyword cobolWatch RUN PROGRAM
|
||||
syn match cobolWatch contained "\<REPLACING\>\s\+\(==\)\@!"
|
||||
" #C22032019: Look for word starting with COMP
|
||||
" syn match cobolWatch \"COMP-[123456XN]"
|
||||
syn match cobolWatch "\<COMP-[123456XN]"
|
||||
|
||||
syn keyword cobolEXECs EXEC END-EXEC
|
||||
|
||||
@ -127,9 +182,15 @@ syn match cobolWatch "88 " contained nextgroup=cobolLine
|
||||
"syn match cobolBadID "\k\+-\($\|[^-A-Z0-9]\)" contained
|
||||
|
||||
syn cluster cobolLine add=cobolCALLs,cobolString,cobolCondFlow
|
||||
syn keyword cobolCALLs CALL END-CALL CANCEL GOBACK PERFORM END-PERFORM INVOKE
|
||||
syn match cobolCALLs "EXIT \+PROGRAM"
|
||||
" #C22032019: Changes for cobolCALLs group to include thru
|
||||
" syn keyword cobolCALLs CALL END-CALL CANCEL GOBACK PERFORM END-PERFORM INVOKE
|
||||
syn keyword cobolCALLs END-CALL CANCEL GOBACK PERFORM END-PERFORM INVOKE THRU
|
||||
" #C22032019: Highlight called program
|
||||
" syn match cobolCALLs \"EXIT \+PROGRAM"
|
||||
syn match cobolCALLs "\<CALL\>"
|
||||
syn match cobolCALLProg /\<CALL\>\s\+"\{0,1\}[A-Z0-9]\+"\{0,1\}/ contains=cobolCALLs
|
||||
syn match cobolExtras /\<VALUE \+\d\+\./hs=s+6,he=e-1
|
||||
syn cluster cobolLine add=cobolCALLProg
|
||||
|
||||
syn match cobolString /"[^"]*\("\|$\)/
|
||||
syn match cobolString /'[^']*\('\|$\)/
|
||||
@ -138,7 +199,7 @@ syn match cobolString /'[^']*\('\|$\)/
|
||||
syn match cobolIndicator "\%7c[D-]" contained
|
||||
|
||||
if exists("cobol_legacy_code")
|
||||
syn region cobolCondFlow contains=ALLBUT,cobolLine,cobolBadLine start="\<\(IF\|INVALID\|END\|EOP\)\>" skip=/\('\|"\)[^"]\{-}\("\|'\|$\)/ end="\." keepend
|
||||
syn region cobolCondFlow contains=ALLBUT,cobolLine start="\<\(IF\|INVALID\|END\|EOP\)\>" skip=/\('\|"\)[^"]\{-}\("\|'\|$\)/ end="\." keepend
|
||||
endif
|
||||
|
||||
" many legacy sources have junk in columns 1-6: must be before others
|
||||
@ -146,7 +207,9 @@ endif
|
||||
if exists("cobol_legacy_code")
|
||||
syn match cobolBadLine "\%73c.*" containedin=ALLBUT,cobolComment
|
||||
else
|
||||
syn match cobolBadLine "\%73c.*" containedin=ALL
|
||||
" #C22032019: Use comment highlighting for bad lines
|
||||
" syn match cobolBadLine \"\%73c.*" containedin=ALL
|
||||
syn match cobolBadLine "\%73c.*" containedin=ALL,cobolInlineComment,cobolComment
|
||||
endif
|
||||
|
||||
" Define the default highlighting.
|
||||
@ -160,31 +223,36 @@ if exists("g:cobol_legacy_code")
|
||||
else
|
||||
hi def link cobolMarker Error
|
||||
endif
|
||||
hi def link cobolCALLs Function
|
||||
hi def link cobolComment Comment
|
||||
hi def link cobolKeys Comment
|
||||
hi def link cobolAreaB Special
|
||||
hi def link cobolCompiler PreProc
|
||||
hi def link cobolCondFlow Special
|
||||
hi def link cobolCopy PreProc
|
||||
hi def link cobolDeclA cobolDecl
|
||||
hi def link cobolDecl Type
|
||||
hi def link cobolExtras Special
|
||||
hi def link cobolGoTo Special
|
||||
hi def link cobolConstant Constant
|
||||
hi def link cobolNumber Constant
|
||||
hi def link cobolPic Constant
|
||||
hi def link cobolReserved Statement
|
||||
hi def link cobolDivision Label
|
||||
hi def link cobolSection Label
|
||||
hi def link cobolParagraph Label
|
||||
hi def link cobolDivisionName Keyword
|
||||
hi def link cobolSectionName Keyword
|
||||
hi def link cobolParagraphName Keyword
|
||||
hi def link cobolString Constant
|
||||
hi def link cobolTodo Todo
|
||||
hi def link cobolWatch Special
|
||||
hi def link cobolIndicator Special
|
||||
hi def link cobolCALLs Function
|
||||
hi def link cobolCALLProg Special
|
||||
hi def link cobolComment Comment
|
||||
hi def link cobolInlineComment Comment
|
||||
hi def link cobolKeys Comment
|
||||
hi def link cobolAreaB Special
|
||||
hi def link cobolCompiler PreProc
|
||||
hi def link cobolCondFlow Special
|
||||
hi def link cobolCopy PreProc
|
||||
hi def link cobolCopyName Special
|
||||
hi def link cobolDeclA cobolDecl
|
||||
hi def link cobolDecl Type
|
||||
hi def link cobolExtras Special
|
||||
hi def link cobolGoTo Special
|
||||
hi def link cobolGoToPara Function
|
||||
hi def link cobolConstant Constant
|
||||
hi def link cobolNumber Constant
|
||||
hi def link cobolPic Constant
|
||||
hi def link cobolReserved Statement
|
||||
hi def link cobolDivision Label
|
||||
hi def link cobolSection Label
|
||||
hi def link cobolParagraph Label
|
||||
hi def link cobolDivisionName Keyword
|
||||
hi def link cobolSectionName Keyword
|
||||
hi def link cobolParagraphName Keyword
|
||||
hi def link cobolString Constant
|
||||
hi def link cobolTodo Todo
|
||||
hi def link cobolWatch Special
|
||||
hi def link cobolIndicator Special
|
||||
hi def link cobolStart Comment
|
||||
|
||||
|
||||
let b:current_syntax = "cobol"
|
||||
|
Reference in New Issue
Block a user