xref: /vim-8.2.3635/runtime/syntax/cobol.vim (revision 63b74a83)
1" Vim syntax file
2" Language:     COBOL
3" Maintainer: Ankit Jain <[email protected]>
4"     (formerly Tim Pope <[email protected]>)
5"     (formerly Davyd Ondrejko <[email protected]>)
6"     (formerly Sitaram Chamarty <[email protected]> and
7"               James Mitchell <[email protected]>)
8" Last Change:    2019 Mar 22
9" Ankit Jain      22.03.2019     Changes & fixes:
10"                                1. Include inline comments
11"                                2. Use comment highlight for bad lines
12"                                3. Change certain 'keywords' to 'matches'
13"                                for additional highlighting
14"                                4. Different highlighting for COPY, GO TO &
15"                                CALL lines
16"                                5. Fix for COMP keyword
17"                                6. Fix for PROCEDURE DIVISION highlighting
18"                                7. Highlight EXIT PROGRAM like STOP RUN
19"                                8. Highlight X & A in PIC clause
20"                                Tag: #C22032019
21
22" quit when a syntax file was already loaded
23if exists("b:current_syntax")
24  finish
25endif
26
27" MOST important - else most of the keywords wont work!
28setlocal isk=@,48-57,-,_
29
30if !exists('g:cobol_inline_comment')
31   let g:cobol_inline_comment=0
32endif
33
34syn case ignore
35
36syn cluster cobolStart      contains=cobolAreaA,cobolAreaB,cobolComment,cobolCompiler
37syn cluster cobolAreaA      contains=cobolParagraph,cobolSection,cobolDivision
38"syn cluster cobolAreaB      contains=
39syn cluster cobolAreaAB     contains=cobolLine
40syn cluster cobolLine       contains=cobolReserved
41syn match   cobolMarker     "^\%( \{,5\}[^ ]\)\@=.\{,6}" nextgroup=@cobolStart
42syn match   cobolSpace      "^ \{6\}"  nextgroup=@cobolStart
43syn match   cobolAreaA      " \{1,4\}"  contained nextgroup=@cobolAreaA,@cobolAreaAB
44syn match   cobolAreaB      " \{5,\}\|- *" contained nextgroup=@cobolAreaB,@cobolAreaAB
45syn match   cobolComment    "[/*C].*$" contained
46syn match   cobolCompiler   "$.*$"     contained
47syn match   cobolLine       ".*$"      contained contains=cobolReserved,@cobolLine
48
49"#C22032019: Fix for PROCEDURE DIVISION USING highlighting, removed . from the
50"end of the regex
51"syn match   cobolDivision       \"[A-Z][A-Z0-9-]*[A-Z0-9]\s\+DIVISION\."he=e-1 contained contains=cobolDivisionName
52syn match   cobolDivision       "[A-Z][A-Z0-9-]*[A-Z0-9]\s\+DIVISION" contained contains=cobolDivisionName
53syn keyword cobolDivisionName   contained IDENTIFICATION ENVIRONMENT DATA PROCEDURE
54syn match   cobolSection        "[A-Z][A-Z0-9-]*[A-Z0-9]\s\+SECTION\."he=e-1  contained contains=cobolSectionName
55syn keyword cobolSectionName    contained CONFIGURATION INPUT-OUTPUT FILE WORKING-STORAGE LOCAL-STORAGE LINKAGE
56syn match   cobolParagraph      "\a[A-Z0-9-]*[A-Z0-9]\.\|\d[A-Z0-9-]*[A-Z]\."he=e-1             contained contains=cobolParagraphName
57syn keyword cobolParagraphName  contained PROGRAM-ID SOURCE-COMPUTER OBJECT-COMPUTER SPECIAL-NAMES FILE-CONTROL I-O-CONTROL
58
59
60"syn match cobolKeys "^\a\{1,6\}" contains=cobolReserved
61"#C22032019: Remove BY, REPLACING, PROGRAM, TO, IN from 'keyword' group and add
62"to 'match' group or other 'keyword' group
63syn keyword cobolReserved contained ACCEPT ACCESS ADD ADDRESS ADVANCING AFTER ALPHABET ALPHABETIC
64syn keyword cobolReserved contained ALPHABETIC-LOWER ALPHABETIC-UPPER ALPHANUMERIC ALPHANUMERIC-EDITED ALS
65syn keyword cobolReserved contained ALTERNATE AND ANY ARE AREA AREAS ASCENDING ASSIGN AT AUTHOR BEFORE BINARY
66syn keyword cobolReserved contained BLANK BLOCK BOTTOM CANCEL CBLL CD CF CH CHARACTER CHARACTERS CLASS
67syn keyword cobolReserved contained CLOCK-UNITS CLOSE COBOL CODE CODE-SET COLLATING COLUMN COMMA COMMON
68syn keyword cobolReserved contained COMMUNICATIONS COMPUTATIONAL COMPUTE CONTENT CONTINUE
69syn keyword cobolReserved contained CONTROL CONVERTING CORR CORRESPONDING COUNT CURRENCY DATE DATE-COMPILED
70syn keyword cobolReserved contained DATE-WRITTEN DAY DAY-OF-WEEK DE DEBUG-CONTENTS DEBUG-ITEM DEBUG-LINE
71syn keyword cobolReserved contained DEBUG-NAME DEBUG-SUB-1 DEBUG-SUB-2 DEBUG-SUB-3 DEBUGGING DECIMAL-POINT
72syn keyword cobolReserved contained DELARATIVES DELETE DELIMITED DELIMITER DEPENDING DESCENDING DESTINATION
73syn keyword cobolReserved contained DETAIL DISABLE DISPLAY DIVIDE DIVISION DOWN DUPLICATES DYNAMIC EGI ELSE EMI
74syn keyword cobolReserved contained ENABLE END-ADD END-COMPUTE END-DELETE END-DIVIDE END-EVALUATE END-IF
75syn keyword cobolReserved contained END-MULTIPLY END-OF-PAGE END-READ END-RECEIVE END-RETURN
76syn keyword cobolReserved contained END-REWRITE END-SEARCH END-START END-STRING END-SUBTRACT END-UNSTRING
77syn keyword cobolReserved contained END-WRITE EQUAL ERROR ESI EVALUATE EVERY EXCEPTION EXIT
78syn keyword cobolReserved contained EXTEND EXTERNAL FALSE FD FILLER FINAL FIRST FOOTING FOR FROM
79syn keyword cobolReserved contained GENERATE GIVING GLOBAL GREATER GROUP HEADING HIGH-VALUE HIGH-VALUES I-O
80syn keyword cobolReserved contained INDEX INDEXED INDICATE INITIAL INITIALIZE
81syn keyword cobolReserved contained INITIATE INPUT INSPECT INSTALLATION INTO IS JUST
82syn keyword cobolReserved contained JUSTIFIED KEY LABEL LAST LEADING LEFT LENGTH LOCK MEMORY
83syn keyword cobolReserved contained MERGE MESSAGE MODE MODULES MOVE MULTIPLE MULTIPLY NATIVE NEGATIVE NEXT NO NOT
84syn keyword cobolReserved contained NUMBER NUMERIC NUMERIC-EDITED OCCURS OF OFF OMITTED ON OPEN
85syn keyword cobolReserved contained OPTIONAL OR ORDER ORGANIZATION OTHER OUTPUT OVERFLOW PACKED-DECIMAL PADDING
86syn keyword cobolReserved contained PAGE PAGE-COUNTER PERFORM PF PH PIC PICTURE PLUS POINTER POSITION POSITIVE
87syn keyword cobolReserved contained PRINTING PROCEDURES PROCEDD PURGE QUEUE QUOTES
88syn keyword cobolReserved contained RANDOM RD READ RECEIVE RECORD RECORDS REDEFINES REEL REFERENCE REFERENCES
89syn keyword cobolReserved contained RELATIVE RELEASE REMAINDER REMOVAL REPLACE REPORT REPORTING
90syn keyword cobolReserved contained REPORTS RERUN RESERVE RESET RETURN RETURNING REVERSED REWIND REWRITE RF RH
91syn keyword cobolReserved contained RIGHT ROUNDED RUN SAME SD SEARCH SECTION SECURITY SEGMENT SEGMENT-LIMITED
92syn keyword cobolReserved contained SELECT SEND SENTENCE SEPARATE SEQUENCE SEQUENTIAL SET SIGN SIZE SORT
93syn keyword cobolReserved contained SORT-MERGE SOURCE STANDARD
94syn keyword cobolReserved contained STANDARD-1 STANDARD-2 START STATUS STOP STRING SUB-QUEUE-1 SUB-QUEUE-2
95syn keyword cobolReserved contained SUB-QUEUE-3 SUBTRACT SUM SUPPRESS SYMBOLIC SYNC SYNCHRONIZED TABLE TALLYING
96syn keyword cobolReserved contained TAPE TERMINAL TERMINATE TEST TEXT THAN THEN THROUGH THRU TIME TIMES TOP
97syn keyword cobolReserved contained TRAILING TRUE TYPE UNIT UNSTRING UNTIL UP UPON USAGE USE USING VALUE VALUES
98syn keyword cobolReserved contained VARYING WHEN WITH WORDS WRITE
99syn match   cobolReserved contained "\<CONTAINS\>"
100syn match   cobolReserved contained "\<\(IF\|INVALID\|END\|EOP\)\>"
101syn match   cobolReserved contained "\<ALL\>"
102" #C22032019: Add BY as match instead of keyword: BY not followed by ==
103syn match   cobolReserved contained "\<BY\>\s\+\(==\)\@!"
104syn match   cobolReserved contained "\<TO\>"
105
106syn cluster cobolLine     add=cobolConstant,cobolNumber,cobolPic
107syn keyword cobolConstant SPACE SPACES NULL ZERO ZEROES ZEROS LOW-VALUE LOW-VALUES
108
109" #C22032019: Fix for many pic clauses
110syn match   cobolNumber       "\<-\=\d*\.\=\d\+\>" contained
111" syn match   cobolPic		\"\<S*9\+\>" contained
112syn match   cobolPic		"\<S*9\+V*9*\>" contained
113syn match   cobolPic		"\<$*\.\=9\+\>" contained
114syn match   cobolPic		"\<Z*\.\=9\+\>" contained
115syn match   cobolPic		"\<V9\+\>" contained
116syn match   cobolPic		"\<9\+V\>" contained
117" syn match   cobolPic		\"\<-\+[Z9]\+\>" contained
118syn match   cobolPic		"\<-*[Z9]\+-*\>" contained
119" #C22032019: Add Z,X and A to cobolPic
120syn match   cobolPic		"\<[ZXA]\+\>" contained
121syn match   cobolTodo		"todo" contained containedin=cobolInlineComment,cobolComment
122
123" For MicroFocus or other inline comments, include this line.
124if g:cobol_inline_comment == 1
125   syn region  cobolInlineComment     start="*>" end="$" contains=cobolTodo,cobolMarker
126   syn cluster cobolLine       add=cobolInlineComment
127endif
128
129syn match   cobolBadLine      "[^ D\*$/-].*" contained
130
131" If comment mark somehow gets into column past Column 7.
132if g:cobol_inline_comment == 1
133   " #C22032019: It is a bad line only if * is not followed by > when inline
134   " comments enabled
135   syn match   cobolBadLine      "\s\+\*\(>\)\@!.*" contained
136else
137   syn match   cobolBadLine      "\s\+\*.*" contained
138endif
139syn cluster cobolStart        add=cobolBadLine
140
141" #C22032019: Different highlighting for GO TO statements
142" syn keyword cobolGoTo		GO GOTO
143syn keyword cobolGoTo		GOTO
144syn match cobolGoTo		/\<GO\>\s\+\<TO\>/
145syn match cobolGoToPara       /\<GO\>\s\+\<TO\>\s\+[A-Z0-9-]\+/ contains=cobolGoTo
146" #C22032019: Highlight copybook name and location in using different group
147" syn keyword cobolCopy		COPY
148syn match cobolCopy		"\<COPY\>\|\<IN\>"
149syn match cobolCopy           "\<REPLACING\>\s\+\(==\)\@="
150syn match cobolCopy           "\<BY\>\s\+\(==\)\@="
151syn match cobolCopyName       "\<COPY\>\s\+[A-Z0-9]\+\(\s\+\<IN\>\s\+[A-Z0-9]\+\)\?" contains=cobolCopy
152syn cluster cobolLine         add=cobolGoToPara,cobolCopyName
153
154" cobolBAD: things that are BAD NEWS!
155syn keyword cobolBAD		ALTER ENTER RENAMES
156
157syn cluster cobolLine       add=cobolGoTo,cobolCopy,cobolBAD,cobolWatch,cobolEXECs
158
159" cobolWatch: things that are important when trying to understand a program
160syn keyword cobolWatch		OCCURS DEPENDING VARYING BINARY COMP REDEFINES
161" #C22032019: Remove REPLACING from cobolWatch 'keyword' group and add to cobolCopy &
162"            cobolWatch 'match' group
163" syn keyword cobolWatch		REPLACING RUN
164syn keyword cobolWatch		RUN PROGRAM
165syn match   cobolWatch contained "\<REPLACING\>\s\+\(==\)\@!"
166" #C22032019: Look for word starting with COMP
167" syn match   cobolWatch		\"COMP-[123456XN]"
168syn match   cobolWatch		"\<COMP-[123456XN]"
169
170syn keyword cobolEXECs		EXEC END-EXEC
171
172
173syn cluster cobolAreaA      add=cobolDeclA
174syn cluster cobolAreaAB     add=cobolDecl
175syn match   cobolDeclA      "\(0\=1\|77\|78\) " contained nextgroup=cobolLine
176syn match   cobolDecl		"[1-4]\d " contained nextgroup=cobolLine
177syn match   cobolDecl		"0\=[2-9] " contained nextgroup=cobolLine
178syn match   cobolDecl		"66 " contained nextgroup=cobolLine
179
180syn match   cobolWatch		"88 " contained nextgroup=cobolLine
181
182"syn match   cobolBadID		"\k\+-\($\|[^-A-Z0-9]\)" contained
183
184syn cluster cobolLine       add=cobolCALLs,cobolString,cobolCondFlow
185" #C22032019: Changes for cobolCALLs group to include thru
186" syn keyword cobolCALLs		CALL END-CALL CANCEL GOBACK PERFORM END-PERFORM INVOKE
187syn keyword cobolCALLs		END-CALL CANCEL GOBACK PERFORM END-PERFORM INVOKE THRU
188" #C22032019: Highlight called program
189" syn match   cobolCALLs		\"EXIT \+PROGRAM"
190syn match   cobolCALLs		"\<CALL\>"
191syn match   cobolCALLProg     /\<CALL\>\s\+"\{0,1\}[A-Z0-9]\+"\{0,1\}/ contains=cobolCALLs
192syn match   cobolExtras       /\<VALUE \+\d\+\./hs=s+6,he=e-1
193syn cluster cobolLine         add=cobolCALLProg
194
195syn match   cobolString       /"[^"]*\("\|$\)/
196syn match   cobolString       /'[^']*\('\|$\)/
197
198"syn region  cobolLine        start="^.\{6}[ D-]" end="$" contains=ALL
199syn match   cobolIndicator   "\%7c[D-]" contained
200
201if exists("cobol_legacy_code")
202  syn region  cobolCondFlow     contains=ALLBUT,cobolLine start="\<\(IF\|INVALID\|END\|EOP\)\>" skip=/\('\|"\)[^"]\{-}\("\|'\|$\)/ end="\." keepend
203endif
204
205" many legacy sources have junk in columns 1-6: must be before others
206" Stuff after column 72 is in error - must be after all other "match" entries
207if exists("cobol_legacy_code")
208    syn match   cobolBadLine      "\%73c.*" containedin=ALLBUT,cobolComment
209else
210    " #C22032019: Use comment highlighting for bad lines
211    " syn match   cobolBadLine      \"\%73c.*" containedin=ALL
212    syn match   cobolBadLine      "\%73c.*" containedin=ALL,cobolInlineComment,cobolComment
213endif
214
215" Define the default highlighting.
216" Only when an item doesn't have highlighting yet
217
218hi def link cobolBAD      Error
219hi def link cobolBadID    Error
220hi def link cobolBadLine  Error
221if exists("g:cobol_legacy_code")
222    hi def link cobolMarker   Comment
223else
224    hi def link cobolMarker   Error
225endif
226hi def link cobolCALLs          Function
227hi def link cobolCALLProg       Special
228hi def link cobolComment        Comment
229hi def link cobolInlineComment  Comment
230hi def link cobolKeys           Comment
231hi def link cobolAreaB          Special
232hi def link cobolCompiler       PreProc
233hi def link cobolCondFlow       Special
234hi def link cobolCopy           PreProc
235hi def link cobolCopyName       Special
236hi def link cobolDeclA          cobolDecl
237hi def link cobolDecl           Type
238hi def link cobolExtras         Special
239hi def link cobolGoTo           Special
240hi def link cobolGoToPara       Function
241hi def link cobolConstant       Constant
242hi def link cobolNumber         Constant
243hi def link cobolPic            Constant
244hi def link cobolReserved       Statement
245hi def link cobolDivision       Label
246hi def link cobolSection        Label
247hi def link cobolParagraph      Label
248hi def link cobolDivisionName   Keyword
249hi def link cobolSectionName    Keyword
250hi def link cobolParagraphName  Keyword
251hi def link cobolString         Constant
252hi def link cobolTodo           Todo
253hi def link cobolWatch          Special
254hi def link cobolIndicator      Special
255hi def link cobolStart          Comment
256
257
258let b:current_syntax = "cobol"
259
260" vim: ts=6 nowrap
261