]>
git.saurik.com Git - wxWidgets.git/blob - src/stc/scintilla/lexers/LexCOBOL.cxx
1 // Scintilla source code edit control
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
19 #include "Scintilla.h"
23 #include "LexAccessor.h"
25 #include "StyleContext.h"
26 #include "CharacterSet.h"
27 #include "LexerModule.h"
30 using namespace Scintilla
;
33 #define IN_DIVISION 0x01
34 #define IN_DECLARATIVES 0x02
35 #define IN_SECTION 0x04
36 #define IN_PARAGRAPH 0x08
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
)
59 for (int i
= 0; i
< 32; ++i
)
67 static void getRange(unsigned int start
,
73 while ((i
< end
- start
+ 1) && (i
< len
-1)) {
74 s
[i
] = static_cast<char>(tolower(styler
[start
+ i
]));
80 static void ColourTo(Accessor
&styler
, unsigned int end
, unsigned int attr
) {
81 styler
.ColourTo(end
, attr
);
85 static int classifyWordCOBOL(unsigned int start
, unsigned int end
, /*WordList &keywords*/WordList
*keywordlists
[], Accessor
&styler
, int nContainment
, bool *bAarea
) {
88 WordList
& a_keywords
= *keywordlists
[0];
89 WordList
& b_keywords
= *keywordlists
[1];
90 WordList
& c_keywords
= *keywordlists
[2];
93 getRange(start
, end
, styler
, s
, sizeof(s
));
95 char chAttr
= SCE_C_IDENTIFIER
;
96 if (isdigit(s
[0]) || (s
[0] == '.') || (s
[0] == 'v')) {
97 chAttr
= SCE_C_NUMBER
;
100 if ((!isdigit(*p
) && (*p
) != 'v') && isCOBOLwordchar(*p
)) {
101 chAttr
= SCE_C_IDENTIFIER
;
108 if (a_keywords
.InList(s
)) {
111 else if (b_keywords
.InList(s
)) {
112 chAttr
= SCE_C_WORD2
;
114 else if (c_keywords
.InList(s
)) {
119 if (strcmp(s
, "division") == 0) {
121 // we've determined the containment, anything else is just ignored for those purposes
123 } else if (strcmp(s
, "declaratives") == 0) {
124 ret
= IN_DIVISION
| IN_DECLARATIVES
;
125 if (nContainment
& IN_DECLARATIVES
)
126 ret
|= NOT_HEADER
| IN_SECTION
;
127 // we've determined the containment, anything else is just ignored for those purposes
129 } else if (strcmp(s
, "section") == 0) {
130 ret
= (nContainment
&~ IN_PARAGRAPH
) | IN_SECTION
;
131 // we've determined the containment, anything else is just ignored for those purposes
133 } else if (strcmp(s
, "end") == 0 && (nContainment
& IN_DECLARATIVES
)) {
134 ret
= IN_DIVISION
| IN_DECLARATIVES
| IN_SECTION
| NOT_HEADER
;
136 ret
= nContainment
| IN_PARAGRAPH
;
139 ColourTo(styler
, end
, chAttr
);
143 static void ColouriseCOBOLDoc(unsigned int startPos
, int length
, int initStyle
, WordList
*keywordlists
[],
146 styler
.StartAt(startPos
);
148 int state
= initStyle
;
149 if (state
== SCE_C_CHARACTER
) // Does not leak onto next line
150 state
= SCE_C_DEFAULT
;
152 char chNext
= styler
[startPos
];
153 unsigned int lengthDoc
= startPos
+ length
;
157 int currentLine
= styler
.GetLine(startPos
);
158 if (currentLine
> 0) {
159 styler
.SetLineState(currentLine
, styler
.GetLineState(currentLine
-1));
160 nContainment
= styler
.GetLineState(currentLine
);
161 nContainment
&= ~NOT_HEADER
;
163 styler
.SetLineState(currentLine
, 0);
167 styler
.StartSegment(startPos
);
168 bool bNewLine
= true;
169 bool bAarea
= !isspacechar(chNext
);
171 for (unsigned int i
= startPos
; i
< lengthDoc
; i
++) {
174 chNext
= styler
.SafeGetCharAt(i
+ 1);
181 if (column
<= 1 && !bAarea
) {
182 bAarea
= !isspacechar(ch
);
184 bool bSetNewLine
= false;
185 if ((ch
== '\r' && chNext
!= '\n') || (ch
== '\n')) {
186 // Trigger on CR only (Mac style) or either on LF from CR+LF (Dos/Win) or on LF alone (Unix)
187 // Avoid triggering two times on Dos/Win
189 if (state
== SCE_C_CHARACTER
) {
190 ColourTo(styler
, i
, state
);
191 state
= SCE_C_DEFAULT
;
193 styler
.SetLineState(currentLine
, nContainment
);
196 if (nContainment
& NOT_HEADER
)
197 nContainment
&= ~(NOT_HEADER
| IN_DECLARATIVES
| IN_SECTION
);
200 if (styler
.IsLeadByte(ch
)) {
201 chNext
= styler
.SafeGetCharAt(i
+ 2);
207 if (state
== SCE_C_DEFAULT
) {
208 if (isCOBOLwordstart(ch
) || (ch
== '$' && isascii(chNext
) && isalpha(chNext
))) {
209 ColourTo(styler
, i
-1, state
);
210 state
= SCE_C_IDENTIFIER
;
211 } else if (column
== 6 && ch
== '*') {
212 // Cobol comment line: asterisk in column 7.
213 ColourTo(styler
, i
-1, state
);
214 state
= SCE_C_COMMENTLINE
;
215 } else if (ch
== '*' && chNext
== '>') {
216 // Cobol inline comment: asterisk, followed by greater than.
217 ColourTo(styler
, i
-1, state
);
218 state
= SCE_C_COMMENTLINE
;
219 } else if (column
== 0 && ch
== '*' && chNext
!= '*') {
220 ColourTo(styler
, i
-1, state
);
221 state
= SCE_C_COMMENTLINE
;
222 } else if (column
== 0 && ch
== '/' && chNext
!= '*') {
223 ColourTo(styler
, i
-1, state
);
224 state
= SCE_C_COMMENTLINE
;
225 } else if (column
== 0 && ch
== '*' && chNext
== '*') {
226 ColourTo(styler
, i
-1, state
);
227 state
= SCE_C_COMMENTDOC
;
228 } else if (column
== 0 && ch
== '/' && chNext
== '*') {
229 ColourTo(styler
, i
-1, state
);
230 state
= SCE_C_COMMENTDOC
;
231 } else if (ch
== '"') {
232 ColourTo(styler
, i
-1, state
);
233 state
= SCE_C_STRING
;
234 } else if (ch
== '\'') {
235 ColourTo(styler
, i
-1, state
);
236 state
= SCE_C_CHARACTER
;
237 } else if (ch
== '?' && column
== 0) {
238 ColourTo(styler
, i
-1, state
);
239 state
= SCE_C_PREPROCESSOR
;
240 } else if (isCOBOLoperator(ch
)) {
241 ColourTo(styler
, i
-1, state
);
242 ColourTo(styler
, i
, SCE_C_OPERATOR
);
244 } else if (state
== SCE_C_IDENTIFIER
) {
245 if (!isCOBOLwordchar(ch
)) {
246 int lStateChange
= classifyWordCOBOL(styler
.GetStartSegment(), i
- 1, keywordlists
, styler
, nContainment
, &bAarea
);
248 if(lStateChange
!= 0) {
249 styler
.SetLineState(currentLine
, lStateChange
);
250 nContainment
= lStateChange
;
253 state
= SCE_C_DEFAULT
;
254 chNext
= styler
.SafeGetCharAt(i
+ 1);
256 state
= SCE_C_STRING
;
257 } else if (ch
== '\'') {
258 state
= SCE_C_CHARACTER
;
259 } else if (isCOBOLoperator(ch
)) {
260 ColourTo(styler
, i
, SCE_C_OPERATOR
);
264 if (state
== SCE_C_PREPROCESSOR
) {
265 if ((ch
== '\r' || ch
== '\n') && !(chPrev
== '\\' || chPrev
== '\r')) {
266 ColourTo(styler
, i
-1, state
);
267 state
= SCE_C_DEFAULT
;
269 } else if (state
== SCE_C_COMMENT
) {
270 if (ch
== '\r' || ch
== '\n') {
271 ColourTo(styler
, i
, state
);
272 state
= SCE_C_DEFAULT
;
274 } else if (state
== SCE_C_COMMENTDOC
) {
275 if (ch
== '\r' || ch
== '\n') {
276 if (((i
> styler
.GetStartSegment() + 2) || (
277 (initStyle
== SCE_C_COMMENTDOC
) &&
278 (styler
.GetStartSegment() == static_cast<unsigned int>(startPos
))))) {
279 ColourTo(styler
, i
, state
);
280 state
= SCE_C_DEFAULT
;
283 } else if (state
== SCE_C_COMMENTLINE
) {
284 if (ch
== '\r' || ch
== '\n') {
285 ColourTo(styler
, i
-1, state
);
286 state
= SCE_C_DEFAULT
;
288 } else if (state
== SCE_C_STRING
) {
290 ColourTo(styler
, i
, state
);
291 state
= SCE_C_DEFAULT
;
293 } else if (state
== SCE_C_CHARACTER
) {
295 ColourTo(styler
, i
, state
);
296 state
= SCE_C_DEFAULT
;
301 bNewLine
= bSetNewLine
;
307 ColourTo(styler
, lengthDoc
- 1, state
);
310 static void FoldCOBOLDoc(unsigned int startPos
, int length
, int, WordList
*[],
312 bool foldCompact
= styler
.GetPropertyInt("fold.compact", 1) != 0;
313 unsigned int endPos
= startPos
+ length
;
314 int visibleChars
= 0;
315 int lineCurrent
= styler
.GetLine(startPos
);
316 int levelPrev
= lineCurrent
> 0 ? styler
.LevelAt(lineCurrent
- 1) & SC_FOLDLEVELNUMBERMASK
: 0xFFF;
317 char chNext
= styler
[startPos
];
319 bool bNewLine
= true;
320 bool bAarea
= !isspacechar(chNext
);
322 bool bComment
= false;
323 for (unsigned int i
= startPos
; i
< endPos
; i
++) {
325 chNext
= styler
.SafeGetCharAt(i
+ 1);
330 bComment
= (ch
== '*' || ch
== '/' || ch
== '?');
332 if (column
<= 1 && !bAarea
) {
333 bAarea
= !isspacechar(ch
);
335 bool atEOL
= (ch
== '\r' && chNext
!= '\n') || (ch
== '\n');
337 int nContainment
= styler
.GetLineState(lineCurrent
);
338 int lev
= CountBits(nContainment
& IN_FLAGS
) | SC_FOLDLEVELBASE
;
339 if (bAarea
&& !bComment
)
341 if (visibleChars
== 0 && foldCompact
)
342 lev
|= SC_FOLDLEVELWHITEFLAG
;
343 if ((bAarea
) && (visibleChars
> 0) && !(nContainment
& NOT_HEADER
) && !bComment
)
344 lev
|= SC_FOLDLEVELHEADERFLAG
;
345 if (lev
!= styler
.LevelAt(lineCurrent
)) {
346 styler
.SetLevel(lineCurrent
, lev
);
348 if ((lev
& SC_FOLDLEVELNUMBERMASK
) <= (levelPrev
& SC_FOLDLEVELNUMBERMASK
)) {
349 // this level is at the same level or less than the previous line
350 // therefore these is nothing for the previous header to collapse, so remove the header
351 styler
.SetLevel(lineCurrent
- 1, levelPrev
& ~SC_FOLDLEVELHEADERFLAG
);
363 if (!isspacechar(ch
))
367 // Fill in the real level of the next line, keeping the current flags as they will be filled in later
368 int flagsNext
= styler
.LevelAt(lineCurrent
) & ~SC_FOLDLEVELNUMBERMASK
;
369 styler
.SetLevel(lineCurrent
, levelPrev
| flagsNext
);
372 static const char * const COBOLWordListDesc
[] = {
379 LexerModule
lmCOBOL(SCLEX_COBOL
, ColouriseCOBOLDoc
, "COBOL", FoldCOBOLDoc
, COBOLWordListDesc
);