]> git.saurik.com Git - wxWidgets.git/blob - src/stc/scintilla/src/LexCOBOL.cxx
d061d5c674a714d5f518cde4825bb80bf1dc059d
[wxWidgets.git] / src / stc / scintilla / src / LexCOBOL.cxx
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 **/
10
11 #include <stdlib.h>
12 #include <string.h>
13 #include <ctype.h>
14 #include <stdio.h>
15 #include <stdarg.h>
16
17 #include "Platform.h"
18
19 #include "PropSet.h"
20 #include "Accessor.h"
21 #include "KeyWords.h"
22 #include "Scintilla.h"
23 #include "SciLexer.h"
24 #include "StyleContext.h"
25
26 #ifdef SCI_NAMESPACE
27 using namespace Scintilla;
28 #endif
29
30 #define IN_DIVISION 0x01
31 #define IN_DECLARATIVES 0x02
32 #define IN_SECTION 0x04
33 #define IN_PARAGRAPH 0x08
34 #define IN_FLAGS 0xF
35 #define NOT_HEADER 0x10
36
37 inline bool isCOBOLoperator(char ch)
38 {
39 return isoperator(ch);
40 }
41
42 inline bool isCOBOLwordchar(char ch)
43 {
44 return isascii(ch) && (isalnum(ch) || ch == '-');
45
46 }
47
48 inline bool isCOBOLwordstart(char ch)
49 {
50 return isascii(ch) && isalnum(ch);
51 }
52
53 static int CountBits(int nBits)
54 {
55 int count = 0;
56 for (int i = 0; i < 32; ++i)
57 {
58 count += nBits & 1;
59 nBits >>= 1;
60 }
61 return count;
62 }
63
64 static void getRange(unsigned int start,
65 unsigned int end,
66 Accessor &styler,
67 char *s,
68 unsigned int len) {
69 unsigned int i = 0;
70 while ((i < end - start + 1) && (i < len-1)) {
71 s[i] = static_cast<char>(tolower(styler[start + i]));
72 i++;
73 }
74 s[i] = '\0';
75 }
76
77 static void ColourTo(Accessor &styler, unsigned int end, unsigned int attr) {
78 styler.ColourTo(end, attr);
79 }
80
81
82 static int classifyWordCOBOL(unsigned int start, unsigned int end, /*WordList &keywords*/WordList *keywordlists[], Accessor &styler, int nContainment, bool *bAarea) {
83 int ret = 0;
84
85 WordList& a_keywords = *keywordlists[0];
86 WordList& b_keywords = *keywordlists[1];
87 WordList& c_keywords = *keywordlists[2];
88
89 char s[100];
90 getRange(start, end, styler, s, sizeof(s));
91
92 char chAttr = SCE_C_IDENTIFIER;
93 if (isdigit(s[0]) || (s[0] == '.')) {
94 chAttr = SCE_C_NUMBER;
95 char *p = s + 1;
96 while (*p) {
97 if (!isdigit(*p) && isCOBOLwordchar(*p)) {
98 chAttr = SCE_C_IDENTIFIER;
99 break;
100 }
101 ++p;
102 }
103 }
104 else {
105 if (a_keywords.InList(s)) {
106 chAttr = SCE_C_WORD;
107 }
108 else if (b_keywords.InList(s)) {
109 chAttr = SCE_C_WORD2;
110 }
111 else if (c_keywords.InList(s)) {
112 chAttr = SCE_C_UUID;
113 }
114 }
115 if (*bAarea) {
116 if (strcmp(s, "division") == 0) {
117 ret = IN_DIVISION;
118 // we've determined the containment, anything else is just ignored for those purposes
119 *bAarea = false;
120 } else if (strcmp(s, "declaratives") == 0) {
121 ret = IN_DIVISION | IN_DECLARATIVES;
122 if (nContainment & IN_DECLARATIVES)
123 ret |= NOT_HEADER | IN_SECTION;
124 // we've determined the containment, anything else is just ignored for those purposes
125 *bAarea = false;
126 } else if (strcmp(s, "section") == 0) {
127 ret = (nContainment &~ IN_PARAGRAPH) | IN_SECTION;
128 // we've determined the containment, anything else is just ignored for those purposes
129 *bAarea = false;
130 } else if (strcmp(s, "end") == 0 && (nContainment & IN_DECLARATIVES)) {
131 ret = IN_DIVISION | IN_DECLARATIVES | IN_SECTION | NOT_HEADER;
132 } else {
133 ret = nContainment | IN_PARAGRAPH;
134 }
135 }
136 ColourTo(styler, end, chAttr);
137 return ret;
138 }
139
140 static void ColouriseCOBOLDoc(unsigned int startPos, int length, int initStyle, WordList *keywordlists[],
141 Accessor &styler) {
142
143 styler.StartAt(startPos);
144
145 int state = initStyle;
146 if (state == SCE_C_CHARACTER) // Does not leak onto next line
147 state = SCE_C_DEFAULT;
148 char chPrev = ' ';
149 char chNext = styler[startPos];
150 unsigned int lengthDoc = startPos + length;
151
152 int nContainment;
153
154 int currentLine = styler.GetLine(startPos);
155 if (currentLine > 0) {
156 styler.SetLineState(currentLine, styler.GetLineState(currentLine-1));
157 nContainment = styler.GetLineState(currentLine);
158 nContainment &= ~NOT_HEADER;
159 } else {
160 styler.SetLineState(currentLine, 0);
161 nContainment = 0;
162 }
163
164 styler.StartSegment(startPos);
165 bool bNewLine = true;
166 bool bAarea = !isspacechar(chNext);
167 int column = 0;
168 for (unsigned int i = startPos; i < lengthDoc; i++) {
169 char ch = chNext;
170
171 chNext = styler.SafeGetCharAt(i + 1);
172
173 ++column;
174
175 if (bNewLine) {
176 column = 0;
177 }
178 if (column <= 1 && !bAarea) {
179 bAarea = !isspacechar(ch);
180 }
181 bool bSetNewLine = false;
182 if ((ch == '\r' && chNext != '\n') || (ch == '\n')) {
183 // Trigger on CR only (Mac style) or either on LF from CR+LF (Dos/Win) or on LF alone (Unix)
184 // Avoid triggering two times on Dos/Win
185 // End of line
186 if (state == SCE_C_CHARACTER) {
187 ColourTo(styler, i, state);
188 state = SCE_C_DEFAULT;
189 }
190 styler.SetLineState(currentLine, nContainment);
191 currentLine++;
192 bSetNewLine = true;
193 if (nContainment & NOT_HEADER)
194 nContainment &= ~(NOT_HEADER | IN_DECLARATIVES | IN_SECTION);
195 }
196
197 if (styler.IsLeadByte(ch)) {
198 chNext = styler.SafeGetCharAt(i + 2);
199 chPrev = ' ';
200 i += 1;
201 continue;
202 }
203
204 if (state == SCE_C_DEFAULT) {
205 if (isCOBOLwordstart(ch) || (ch == '$' && isalpha(chNext))) {
206 ColourTo(styler, i-1, state);
207 state = SCE_C_IDENTIFIER;
208 } else if (column == 0 && ch == '*' && chNext != '*') {
209 ColourTo(styler, i-1, state);
210 state = SCE_C_COMMENTLINE;
211 } else if (column == 0 && ch == '/' && chNext != '*') {
212 ColourTo(styler, i-1, state);
213 state = SCE_C_COMMENTLINE;
214 } else if (column == 0 && ch == '*' && chNext == '*') {
215 ColourTo(styler, i-1, state);
216 state = SCE_C_COMMENTDOC;
217 } else if (column == 0 && ch == '/' && chNext == '*') {
218 ColourTo(styler, i-1, state);
219 state = SCE_C_COMMENTDOC;
220 } else if (ch == '"') {
221 ColourTo(styler, i-1, state);
222 state = SCE_C_STRING;
223 } else if (ch == '\'') {
224 ColourTo(styler, i-1, state);
225 state = SCE_C_CHARACTER;
226 } else if (ch == '?' && column == 0) {
227 ColourTo(styler, i-1, state);
228 state = SCE_C_PREPROCESSOR;
229 } else if (isCOBOLoperator(ch)) {
230 ColourTo(styler, i-1, state);
231 ColourTo(styler, i, SCE_C_OPERATOR);
232 }
233 } else if (state == SCE_C_IDENTIFIER) {
234 if (!isCOBOLwordchar(ch)) {
235 int lStateChange = classifyWordCOBOL(styler.GetStartSegment(), i - 1, keywordlists, styler, nContainment, &bAarea);
236
237 if(lStateChange != 0) {
238 styler.SetLineState(currentLine, lStateChange);
239 nContainment = lStateChange;
240 }
241
242 state = SCE_C_DEFAULT;
243 chNext = styler.SafeGetCharAt(i + 1);
244 if (ch == '"') {
245 state = SCE_C_STRING;
246 } else if (ch == '\'') {
247 state = SCE_C_CHARACTER;
248 } else if (isCOBOLoperator(ch)) {
249 ColourTo(styler, i, SCE_C_OPERATOR);
250 }
251 }
252 } else {
253 if (state == SCE_C_PREPROCESSOR) {
254 if ((ch == '\r' || ch == '\n') && !(chPrev == '\\' || chPrev == '\r')) {
255 ColourTo(styler, i-1, state);
256 state = SCE_C_DEFAULT;
257 }
258 } else if (state == SCE_C_COMMENT) {
259 if (ch == '\r' || ch == '\n') {
260 ColourTo(styler, i, state);
261 state = SCE_C_DEFAULT;
262 }
263 } else if (state == SCE_C_COMMENTDOC) {
264 if (ch == '\r' || ch == '\n') {
265 if (((i > styler.GetStartSegment() + 2) || (
266 (initStyle == SCE_C_COMMENTDOC) &&
267 (styler.GetStartSegment() == static_cast<unsigned int>(startPos))))) {
268 ColourTo(styler, i, state);
269 state = SCE_C_DEFAULT;
270 }
271 }
272 } else if (state == SCE_C_COMMENTLINE) {
273 if (ch == '\r' || ch == '\n') {
274 ColourTo(styler, i-1, state);
275 state = SCE_C_DEFAULT;
276 }
277 } else if (state == SCE_C_STRING) {
278 if (ch == '"') {
279 ColourTo(styler, i, state);
280 state = SCE_C_DEFAULT;
281 }
282 } else if (state == SCE_C_CHARACTER) {
283 if (ch == '\'') {
284 ColourTo(styler, i, state);
285 state = SCE_C_DEFAULT;
286 }
287 }
288 }
289 chPrev = ch;
290 bNewLine = bSetNewLine;
291 if (bNewLine)
292 {
293 bAarea = false;
294 }
295 }
296 ColourTo(styler, lengthDoc - 1, state);
297 }
298
299 static void FoldCOBOLDoc(unsigned int startPos, int length, int, WordList *[],
300 Accessor &styler) {
301 bool foldCompact = styler.GetPropertyInt("fold.compact", 1) != 0;
302 unsigned int endPos = startPos + length;
303 int visibleChars = 0;
304 int lineCurrent = styler.GetLine(startPos);
305 int levelPrev = lineCurrent > 0 ? styler.LevelAt(lineCurrent - 1) & SC_FOLDLEVELNUMBERMASK : 0xFFF;
306 char chNext = styler[startPos];
307
308 bool bNewLine = true;
309 bool bAarea = !isspacechar(chNext);
310 int column = 0;
311 bool bComment = false;
312 for (unsigned int i = startPos; i < endPos; i++) {
313 char ch = chNext;
314 chNext = styler.SafeGetCharAt(i + 1);
315 ++column;
316
317 if (bNewLine) {
318 column = 0;
319 bComment = (ch == '*' || ch == '/' || ch == '?');
320 }
321 if (column <= 1 && !bAarea) {
322 bAarea = !isspacechar(ch);
323 }
324 bool atEOL = (ch == '\r' && chNext != '\n') || (ch == '\n');
325 if (atEOL) {
326 int nContainment = styler.GetLineState(lineCurrent);
327 int lev = CountBits(nContainment & IN_FLAGS) | SC_FOLDLEVELBASE;
328 if (bAarea && !bComment)
329 --lev;
330 if (visibleChars == 0 && foldCompact)
331 lev |= SC_FOLDLEVELWHITEFLAG;
332 if ((bAarea) && (visibleChars > 0) && !(nContainment & NOT_HEADER) && !bComment)
333 lev |= SC_FOLDLEVELHEADERFLAG;
334 if (lev != styler.LevelAt(lineCurrent)) {
335 styler.SetLevel(lineCurrent, lev);
336 }
337 if ((lev & SC_FOLDLEVELNUMBERMASK) <= (levelPrev & SC_FOLDLEVELNUMBERMASK)) {
338 // this level is at the same level or less than the previous line
339 // therefore these is nothing for the previous header to collapse, so remove the header
340 styler.SetLevel(lineCurrent - 1, levelPrev & ~SC_FOLDLEVELHEADERFLAG);
341 }
342 levelPrev = lev;
343 visibleChars = 0;
344 bAarea = false;
345 bNewLine = true;
346 lineCurrent++;
347 } else {
348 bNewLine = false;
349 }
350
351
352 if (!isspacechar(ch))
353 visibleChars++;
354 }
355
356 // Fill in the real level of the next line, keeping the current flags as they will be filled in later
357 int flagsNext = styler.LevelAt(lineCurrent) & ~SC_FOLDLEVELNUMBERMASK;
358 styler.SetLevel(lineCurrent, levelPrev | flagsNext);
359 }
360
361 static const char * const COBOLWordListDesc[] = {
362 "A Keywords",
363 "B Keywords",
364 "Extended Keywords",
365 0
366 };
367
368 LexerModule lmCOBOL(SCLEX_COBOL, ColouriseCOBOLDoc, "COBOL", FoldCOBOLDoc, COBOLWordListDesc);