From bc9757916ed09763d96283ee62dbed58bd713a11 Mon Sep 17 00:00:00 2001 From: Adam Stankiewicz Date: Tue, 6 Oct 2020 18:54:19 +0200 Subject: Add all vim filetypes --- syntax/cobol.vim | 264 +++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 264 insertions(+) create mode 100644 syntax/cobol.vim (limited to 'syntax/cobol.vim') diff --git a/syntax/cobol.vim b/syntax/cobol.vim new file mode 100644 index 00000000..d3a723f3 --- /dev/null +++ b/syntax/cobol.vim @@ -0,0 +1,264 @@ +if !exists('g:polyglot_disabled') || index(g:polyglot_disabled, 'cobol') == -1 + +" Vim syntax file +" Language: COBOL +" Maintainer: Ankit Jain +" (formerly Tim Pope ) +" (formerly Davyd Ondrejko ) +" (formerly Sitaram Chamarty and +" James Mitchell ) +" 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") + finish +endif + +" MOST important - else most of the keywords wont work! +setlocal isk=@,48-57,-,_ + +if !exists('g:cobol_inline_comment') + let g:cobol_inline_comment=0 +endif + +syn case ignore + +syn cluster cobolStart contains=cobolAreaA,cobolAreaB,cobolComment,cobolCompiler +syn cluster cobolAreaA contains=cobolParagraph,cobolSection,cobolDivision +"syn cluster cobolAreaB contains= +syn cluster cobolAreaAB contains=cobolLine +syn cluster cobolLine contains=cobolReserved +syn match cobolMarker "^\%( \{,5\}[^ ]\)\@=.\{,6}" nextgroup=@cobolStart +syn match cobolSpace "^ \{6\}" nextgroup=@cobolStart +syn match cobolAreaA " \{1,4\}" contained nextgroup=@cobolAreaA,@cobolAreaAB +syn match cobolAreaB " \{5,\}\|- *" contained nextgroup=@cobolAreaB,@cobolAreaAB +syn match cobolComment "[/*C].*$" contained +syn match cobolCompiler "$.*$" contained +syn match cobolLine ".*$" contained contains=cobolReserved,@cobolLine + +"#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 +syn match cobolParagraph "\a[A-Z0-9-]*[A-Z0-9]\.\|\d[A-Z0-9-]*[A-Z]\."he=e-1 contained contains=cobolParagraphName +syn keyword cobolParagraphName contained PROGRAM-ID SOURCE-COMPUTER OBJECT-COMPUTER SPECIAL-NAMES FILE-CONTROL I-O-CONTROL + + +"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 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 +syn keyword cobolReserved contained DATE-WRITTEN DAY DAY-OF-WEEK DE DEBUG-CONTENTS DEBUG-ITEM DEBUG-LINE +syn keyword cobolReserved contained DEBUG-NAME DEBUG-SUB-1 DEBUG-SUB-2 DEBUG-SUB-3 DEBUGGING DECIMAL-POINT +syn keyword cobolReserved contained DELARATIVES DELETE DELIMITED DELIMITER DEPENDING DESCENDING DESTINATION +syn keyword cobolReserved contained DETAIL DISABLE DISPLAY DIVIDE DIVISION DOWN DUPLICATES DYNAMIC EGI ELSE EMI +syn keyword cobolReserved contained ENABLE END-ADD END-COMPUTE END-DELETE END-DIVIDE END-EVALUATE END-IF +syn keyword cobolReserved contained END-MULTIPLY END-OF-PAGE END-READ END-RECEIVE END-RETURN +syn keyword cobolReserved contained END-REWRITE END-SEARCH END-START END-STRING END-SUBTRACT END-UNSTRING +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 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 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 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 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 "\" +syn match cobolReserved contained "\<\(IF\|INVALID\|END\|EOP\)\>" +syn match cobolReserved contained "\" +" #C22032019: Add BY as match instead of keyword: BY not followed by == +syn match cobolReserved contained "\\s\+\(==\)\@!" +syn match cobolReserved contained "\" + +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 \"\" contained +syn match cobolPic "\" contained +syn match cobolPic "\<$*\.\=9\+\>" contained +syn match cobolPic "\" contained +syn match cobolPic "\" contained +syn match cobolPic "\<9\+V\>" contained +" 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. +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. +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 + +" #C22032019: Different highlighting for GO TO statements +" syn keyword cobolGoTo GO GOTO +syn keyword cobolGoTo GOTO +syn match cobolGoTo /\\s\+\/ +syn match cobolGoToPara /\\s\+\\s\+[A-Z0-9-]\+/ contains=cobolGoTo +" #C22032019: Highlight copybook name and location in using different group +" syn keyword cobolCopy COPY +syn match cobolCopy "\\|\" +syn match cobolCopy "\\s\+\(==\)\@=" +syn match cobolCopy "\\s\+\(==\)\@=" +syn match cobolCopyName "\\s\+[A-Z0-9]\+\(\s\+\\s\+[A-Z0-9]\+\)\?" contains=cobolCopy +syn cluster cobolLine add=cobolGoToPara,cobolCopyName + +" cobolBAD: things that are BAD NEWS! +syn keyword cobolBAD ALTER ENTER RENAMES + +syn cluster cobolLine add=cobolGoTo,cobolCopy,cobolBAD,cobolWatch,cobolEXECs + +" cobolWatch: things that are important when trying to understand a program +syn keyword cobolWatch OCCURS DEPENDING VARYING BINARY COMP REDEFINES +" #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 "\\s\+\(==\)\@!" +" #C22032019: Look for word starting with COMP +" syn match cobolWatch \"COMP-[123456XN]" +syn match cobolWatch "\" +syn match cobolCALLProg /\\s\+"\{0,1\}[A-Z0-9]\+"\{0,1\}/ contains=cobolCALLs +syn match cobolExtras /\