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