Merge pull request #826 from kugel-/doxygen-fixes2
[geany-mirror.git] / scintilla / lexers / LexCOBOL.cxx
blob3150e33385b9fabca06511e8c52ab5f35c00cc0d
1 // Scintilla source code edit control
2 /** @file LexCOBOL.cxx
3 ** Lexer for COBOL
4 ** Based on LexPascal.cxx
5 ** Written by Laurent le Tynevez
6 ** Updated by Simon Steele <s.steele@pnotepad.org> September 2002
7 ** Updated by Mathias Rauen <scite@madshi.net> May 2003 (Delphi adjustments)
8 ** Updated by Rod Falck, Aug 2006 Converted to COBOL
9 **/
11 #include <stdlib.h>
12 #include <string.h>
13 #include <stdio.h>
14 #include <stdarg.h>
15 #include <assert.h>
16 #include <ctype.h>
18 #include "ILexer.h"
19 #include "Scintilla.h"
20 #include "SciLexer.h"
22 #include "WordList.h"
23 #include "LexAccessor.h"
24 #include "Accessor.h"
25 #include "StyleContext.h"
26 #include "CharacterSet.h"
27 #include "LexerModule.h"
29 #ifdef SCI_NAMESPACE
30 using namespace Scintilla;
31 #endif
33 #define IN_DIVISION 0x01
34 #define IN_DECLARATIVES 0x02
35 #define IN_SECTION 0x04
36 #define IN_PARAGRAPH 0x08
37 #define IN_FLAGS 0xF
38 #define NOT_HEADER 0x10
40 inline bool isCOBOLoperator(char ch)
42 return isoperator(ch);
45 inline bool isCOBOLwordchar(char ch)
47 return IsASCII(ch) && (isalnum(ch) || ch == '-');
51 inline bool isCOBOLwordstart(char ch)
53 return IsASCII(ch) && isalnum(ch);
56 static int CountBits(int nBits)
58 int count = 0;
59 for (int i = 0; i < 32; ++i)
61 count += nBits & 1;
62 nBits >>= 1;
64 return count;
67 static void getRange(Sci_PositionU start,
68 Sci_PositionU end,
69 Accessor &styler,
70 char *s,
71 Sci_PositionU len) {
72 Sci_PositionU i = 0;
73 while ((i < end - start + 1) && (i < len-1)) {
74 s[i] = static_cast<char>(tolower(styler[start + i]));
75 i++;
77 s[i] = '\0';
80 static void ColourTo(Accessor &styler, Sci_PositionU end, unsigned int attr) {
81 styler.ColourTo(end, attr);
85 static int classifyWordCOBOL(Sci_PositionU start, Sci_PositionU end, /*WordList &keywords*/WordList *keywordlists[], Accessor &styler, int nContainment, bool *bAarea) {
86 int ret = 0;
88 WordList& a_keywords = *keywordlists[0];
89 WordList& b_keywords = *keywordlists[1];
90 WordList& c_keywords = *keywordlists[2];
92 char s[100];
93 s[0] = '\0';
94 s[1] = '\0';
95 getRange(start, end, styler, s, sizeof(s));
97 char chAttr = SCE_C_IDENTIFIER;
98 if (isdigit(s[0]) || (s[0] == '.') || (s[0] == 'v')) {
99 chAttr = SCE_C_NUMBER;
100 char *p = s + 1;
101 while (*p) {
102 if ((!isdigit(*p) && (*p) != 'v') && isCOBOLwordchar(*p)) {
103 chAttr = SCE_C_IDENTIFIER;
104 break;
106 ++p;
109 else {
110 if (a_keywords.InList(s)) {
111 chAttr = SCE_C_WORD;
113 else if (b_keywords.InList(s)) {
114 chAttr = SCE_C_WORD2;
116 else if (c_keywords.InList(s)) {
117 chAttr = SCE_C_UUID;
120 if (*bAarea) {
121 if (strcmp(s, "division") == 0) {
122 ret = IN_DIVISION;
123 // we've determined the containment, anything else is just ignored for those purposes
124 *bAarea = false;
125 } else if (strcmp(s, "declaratives") == 0) {
126 ret = IN_DIVISION | IN_DECLARATIVES;
127 if (nContainment & IN_DECLARATIVES)
128 ret |= NOT_HEADER | IN_SECTION;
129 // we've determined the containment, anything else is just ignored for those purposes
130 *bAarea = false;
131 } else if (strcmp(s, "section") == 0) {
132 ret = (nContainment &~ IN_PARAGRAPH) | IN_SECTION;
133 // we've determined the containment, anything else is just ignored for those purposes
134 *bAarea = false;
135 } else if (strcmp(s, "end") == 0 && (nContainment & IN_DECLARATIVES)) {
136 ret = IN_DIVISION | IN_DECLARATIVES | IN_SECTION | NOT_HEADER;
137 } else {
138 ret = nContainment | IN_PARAGRAPH;
141 ColourTo(styler, end, chAttr);
142 return ret;
145 static void ColouriseCOBOLDoc(Sci_PositionU startPos, Sci_Position length, int initStyle, WordList *keywordlists[],
146 Accessor &styler) {
148 styler.StartAt(startPos);
150 int state = initStyle;
151 if (state == SCE_C_CHARACTER) // Does not leak onto next line
152 state = SCE_C_DEFAULT;
153 char chPrev = ' ';
154 char chNext = styler[startPos];
155 Sci_PositionU lengthDoc = startPos + length;
157 int nContainment;
159 Sci_Position currentLine = styler.GetLine(startPos);
160 if (currentLine > 0) {
161 styler.SetLineState(currentLine, styler.GetLineState(currentLine-1));
162 nContainment = styler.GetLineState(currentLine);
163 nContainment &= ~NOT_HEADER;
164 } else {
165 styler.SetLineState(currentLine, 0);
166 nContainment = 0;
169 styler.StartSegment(startPos);
170 bool bNewLine = true;
171 bool bAarea = !isspacechar(chNext);
172 int column = 0;
173 for (Sci_PositionU i = startPos; i < lengthDoc; i++) {
174 char ch = chNext;
176 chNext = styler.SafeGetCharAt(i + 1);
178 ++column;
180 if (bNewLine) {
181 column = 0;
183 if (column <= 1 && !bAarea) {
184 bAarea = !isspacechar(ch);
186 bool bSetNewLine = false;
187 if ((ch == '\r' && chNext != '\n') || (ch == '\n')) {
188 // Trigger on CR only (Mac style) or either on LF from CR+LF (Dos/Win) or on LF alone (Unix)
189 // Avoid triggering two times on Dos/Win
190 // End of line
191 if (state == SCE_C_CHARACTER) {
192 ColourTo(styler, i, state);
193 state = SCE_C_DEFAULT;
195 styler.SetLineState(currentLine, nContainment);
196 currentLine++;
197 bSetNewLine = true;
198 if (nContainment & NOT_HEADER)
199 nContainment &= ~(NOT_HEADER | IN_DECLARATIVES | IN_SECTION);
202 if (styler.IsLeadByte(ch)) {
203 chNext = styler.SafeGetCharAt(i + 2);
204 chPrev = ' ';
205 i += 1;
206 continue;
209 if (state == SCE_C_DEFAULT) {
210 if (isCOBOLwordstart(ch) || (ch == '$' && IsASCII(chNext) && isalpha(chNext))) {
211 ColourTo(styler, i-1, state);
212 state = SCE_C_IDENTIFIER;
213 } else if (column == 6 && ch == '*') {
214 // Cobol comment line: asterisk in column 7.
215 ColourTo(styler, i-1, state);
216 state = SCE_C_COMMENTLINE;
217 } else if (ch == '*' && chNext == '>') {
218 // Cobol inline comment: asterisk, followed by greater than.
219 ColourTo(styler, i-1, state);
220 state = SCE_C_COMMENTLINE;
221 } else if (column == 0 && ch == '*' && chNext != '*') {
222 ColourTo(styler, i-1, state);
223 state = SCE_C_COMMENTLINE;
224 } else if (column == 0 && ch == '/' && chNext != '*') {
225 ColourTo(styler, i-1, state);
226 state = SCE_C_COMMENTLINE;
227 } else if (column == 0 && ch == '*' && chNext == '*') {
228 ColourTo(styler, i-1, state);
229 state = SCE_C_COMMENTDOC;
230 } else if (column == 0 && ch == '/' && chNext == '*') {
231 ColourTo(styler, i-1, state);
232 state = SCE_C_COMMENTDOC;
233 } else if (ch == '"') {
234 ColourTo(styler, i-1, state);
235 state = SCE_C_STRING;
236 } else if (ch == '\'') {
237 ColourTo(styler, i-1, state);
238 state = SCE_C_CHARACTER;
239 } else if (ch == '?' && column == 0) {
240 ColourTo(styler, i-1, state);
241 state = SCE_C_PREPROCESSOR;
242 } else if (isCOBOLoperator(ch)) {
243 ColourTo(styler, i-1, state);
244 ColourTo(styler, i, SCE_C_OPERATOR);
246 } else if (state == SCE_C_IDENTIFIER) {
247 if (!isCOBOLwordchar(ch)) {
248 int lStateChange = classifyWordCOBOL(styler.GetStartSegment(), i - 1, keywordlists, styler, nContainment, &bAarea);
250 if(lStateChange != 0) {
251 styler.SetLineState(currentLine, lStateChange);
252 nContainment = lStateChange;
255 state = SCE_C_DEFAULT;
256 chNext = styler.SafeGetCharAt(i + 1);
257 if (ch == '"') {
258 state = SCE_C_STRING;
259 } else if (ch == '\'') {
260 state = SCE_C_CHARACTER;
261 } else if (isCOBOLoperator(ch)) {
262 ColourTo(styler, i, SCE_C_OPERATOR);
265 } else {
266 if (state == SCE_C_PREPROCESSOR) {
267 if ((ch == '\r' || ch == '\n') && !(chPrev == '\\' || chPrev == '\r')) {
268 ColourTo(styler, i-1, state);
269 state = SCE_C_DEFAULT;
271 } else if (state == SCE_C_COMMENT) {
272 if (ch == '\r' || ch == '\n') {
273 ColourTo(styler, i, state);
274 state = SCE_C_DEFAULT;
276 } else if (state == SCE_C_COMMENTDOC) {
277 if (ch == '\r' || ch == '\n') {
278 if (((i > styler.GetStartSegment() + 2) || (
279 (initStyle == SCE_C_COMMENTDOC) &&
280 (styler.GetStartSegment() == static_cast<Sci_PositionU>(startPos))))) {
281 ColourTo(styler, i, state);
282 state = SCE_C_DEFAULT;
285 } else if (state == SCE_C_COMMENTLINE) {
286 if (ch == '\r' || ch == '\n') {
287 ColourTo(styler, i-1, state);
288 state = SCE_C_DEFAULT;
290 } else if (state == SCE_C_STRING) {
291 if (ch == '"') {
292 ColourTo(styler, i, state);
293 state = SCE_C_DEFAULT;
295 } else if (state == SCE_C_CHARACTER) {
296 if (ch == '\'') {
297 ColourTo(styler, i, state);
298 state = SCE_C_DEFAULT;
302 chPrev = ch;
303 bNewLine = bSetNewLine;
304 if (bNewLine)
306 bAarea = false;
309 ColourTo(styler, lengthDoc - 1, state);
312 static void FoldCOBOLDoc(Sci_PositionU startPos, Sci_Position length, int, WordList *[],
313 Accessor &styler) {
314 bool foldCompact = styler.GetPropertyInt("fold.compact", 1) != 0;
315 Sci_PositionU endPos = startPos + length;
316 int visibleChars = 0;
317 Sci_Position lineCurrent = styler.GetLine(startPos);
318 int levelPrev = lineCurrent > 0 ? styler.LevelAt(lineCurrent - 1) & SC_FOLDLEVELNUMBERMASK : 0xFFF;
319 char chNext = styler[startPos];
321 bool bNewLine = true;
322 bool bAarea = !isspacechar(chNext);
323 int column = 0;
324 bool bComment = false;
325 for (Sci_PositionU i = startPos; i < endPos; i++) {
326 char ch = chNext;
327 chNext = styler.SafeGetCharAt(i + 1);
328 ++column;
330 if (bNewLine) {
331 column = 0;
332 bComment = (ch == '*' || ch == '/' || ch == '?');
334 if (column <= 1 && !bAarea) {
335 bAarea = !isspacechar(ch);
337 bool atEOL = (ch == '\r' && chNext != '\n') || (ch == '\n');
338 if (atEOL) {
339 int nContainment = styler.GetLineState(lineCurrent);
340 int lev = CountBits(nContainment & IN_FLAGS) | SC_FOLDLEVELBASE;
341 if (bAarea && !bComment)
342 --lev;
343 if (visibleChars == 0 && foldCompact)
344 lev |= SC_FOLDLEVELWHITEFLAG;
345 if ((bAarea) && (visibleChars > 0) && !(nContainment & NOT_HEADER) && !bComment)
346 lev |= SC_FOLDLEVELHEADERFLAG;
347 if (lev != styler.LevelAt(lineCurrent)) {
348 styler.SetLevel(lineCurrent, lev);
350 if ((lev & SC_FOLDLEVELNUMBERMASK) <= (levelPrev & SC_FOLDLEVELNUMBERMASK)) {
351 // this level is at the same level or less than the previous line
352 // therefore these is nothing for the previous header to collapse, so remove the header
353 styler.SetLevel(lineCurrent - 1, levelPrev & ~SC_FOLDLEVELHEADERFLAG);
355 levelPrev = lev;
356 visibleChars = 0;
357 bAarea = false;
358 bNewLine = true;
359 lineCurrent++;
360 } else {
361 bNewLine = false;
365 if (!isspacechar(ch))
366 visibleChars++;
369 // Fill in the real level of the next line, keeping the current flags as they will be filled in later
370 int flagsNext = styler.LevelAt(lineCurrent) & ~SC_FOLDLEVELNUMBERMASK;
371 styler.SetLevel(lineCurrent, levelPrev | flagsNext);
374 static const char * const COBOLWordListDesc[] = {
375 "A Keywords",
376 "B Keywords",
377 "Extended Keywords",
381 LexerModule lmCOBOL(SCLEX_COBOL, ColouriseCOBOLDoc, "COBOL", FoldCOBOLDoc, COBOLWordListDesc);