Skip to content

Commit f294bd6

Browse files
authored
WI #1991 Check reference modifiers literals (#2033)
* WI #1991 Add checks to reference modifiers * WI #1991 Correct tabs * WI #1991 Clarify the diagnostic message and uncomment a line in test * WI #1991 Fix previous commit by replecaing a deleted AddError call
1 parent 1e0c13c commit f294bd6

File tree

5 files changed

+199
-3
lines changed

5 files changed

+199
-3
lines changed

TypeCobol.Test/Parser/CodeElements/SEARCH.cbl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,8 @@ SEARCH x VARYING y
55
SEARCH ALL x VARYING y
66
* ERROR p409: identifier-1 must not be subscripted or reference-modified.
77
SEARCH identifier1 (ALL)
8-
SEARCH identifier1 (0:1)
9-
SEARCH identifier1 (ALL)(0:1)
8+
SEARCH identifier1 (1:1)
9+
SEARCH identifier1 (ALL)(1:1)
1010
* explicit scope
1111
SEARCH ALL someIdentifier
1212
AT END
Lines changed: 64 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,64 @@
1+
IDENTIFICATION DIVISION.
2+
PROGRAM-ID. Pgm.
3+
DATA DIVISION.
4+
WORKING-STORAGE SECTION.
5+
01 item PIC X(20).
6+
01 part PIC X(20).
7+
01 var0 PIC 9 VALUE 0.
8+
01 var1 PIC 9 VALUE 1.
9+
10+
PROCEDURE DIVISION.
11+
* OK this is a shorthand
12+
MOVE item(2:) TO part
13+
* KO zero position
14+
MOVE item(0:) TO part
15+
* KO negative position
16+
MOVE item(-1:) TO part
17+
* KO by a previous step
18+
MOVE item(:2) TO part
19+
20+
* KO zero position
21+
MOVE item(0:5) TO part
22+
* KO zero length
23+
MOVE item(1:0) TO part
24+
* KO*2 zero values
25+
MOVE item(0:0) TO part
26+
* KO negative position
27+
MOVE item(-1:5) TO part
28+
* KO negative length
29+
MOVE item(1:-5) TO part
30+
* KO*2 negative values
31+
MOVE item(-1:-5) TO part
32+
* OK
33+
MOVE item(1.32:5) TO part
34+
* OK
35+
MOVE item(1:5.84) TO part
36+
* OK
37+
MOVE item(1.32:5.84) TO part
38+
* KO zero position
39+
MOVE item(0.0:5) TO part
40+
* KO zero length
41+
MOVE item(1:0.0) TO part
42+
* KO*2 zero values
43+
MOVE item(0.0:0.0) TO part
44+
* KO negative position
45+
MOVE item(-1.32:5) TO part
46+
* KO negative length
47+
MOVE item(1:-5.84) TO part
48+
* KO*2 negative values
49+
MOVE item(-1.32:-5.84) TO part
50+
51+
* OK Variables are not checked
52+
MOVE item(var0:) TO part
53+
MOVE item(var1:) TO part
54+
MOVE item(2:var0) TO part
55+
MOVE item(2:var1) TO part
56+
57+
* OK Expressions are not checked
58+
MOVE item(2 * 3 : 4 ) TO part
59+
MOVE item(2 : 4 * 2 ) TO part
60+
MOVE item(2 * 2 : 4 * 2 ) TO part
61+
MOVE item(-2 + 1 : 2 ) TO part
62+
MOVE item(2 : 4 * -2) TO part
63+
.
64+
END PROGRAM Pgm.
Lines changed: 83 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,83 @@
1+
 IDENTIFICATION DIVISION.
2+
PROGRAM-ID. Pgm.
3+
DATA DIVISION.
4+
WORKING-STORAGE SECTION.
5+
01 item PIC X(20).
6+
01 part PIC X(20).
7+
01 var0 PIC 9 VALUE 0.
8+
01 var1 PIC 9 VALUE 1.
9+
10+
PROCEDURE DIVISION.
11+
* OK this is a shorthand
12+
MOVE item(2:) TO part
13+
* KO zero position
14+
Line 14[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
15+
MOVE item(0:) TO part
16+
* KO negative position
17+
Line 16[22,23] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
18+
MOVE item(-1:) TO part
19+
* KO by a previous step
20+
Line 18[21,21] <27, Error, Syntax> - Syntax error : mismatched input '(' expecting TO
21+
MOVE item(:2) TO part
22+
23+
* KO zero position
24+
Line 21[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
25+
MOVE item(0:5) TO part
26+
* KO zero length
27+
Line 23[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
28+
MOVE item(1:0) TO part
29+
* KO*2 zero values
30+
Line 25[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
31+
Line 25[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
32+
MOVE item(0:0) TO part
33+
* KO negative position
34+
Line 27[22,23] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
35+
MOVE item(-1:5) TO part
36+
* KO negative length
37+
Line 29[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
38+
MOVE item(1:-5) TO part
39+
* KO*2 negative values
40+
Line 31[22,23] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
41+
Line 31[22,23] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
42+
MOVE item(-1:-5) TO part
43+
* OK
44+
MOVE item(1.32:5) TO part
45+
* OK
46+
MOVE item(1:5.84) TO part
47+
* OK
48+
MOVE item(1.32:5.84) TO part
49+
* KO zero position
50+
Line 39[22,24] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
51+
MOVE item(0.0:5) TO part
52+
* KO zero length
53+
Line 41[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
54+
MOVE item(1:0.0) TO part
55+
* KO*2 zero values
56+
Line 43[22,24] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
57+
Line 43[22,24] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
58+
MOVE item(0.0:0.0) TO part
59+
* KO negative position
60+
Line 45[22,26] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
61+
MOVE item(-1.32:5) TO part
62+
* KO negative length
63+
Line 47[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
64+
MOVE item(1:-5.84) TO part
65+
* KO*2 negative values
66+
Line 49[22,26] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
67+
Line 49[22,26] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
68+
MOVE item(-1.32:-5.84) TO part
69+
70+
* OK Variables are not checked
71+
MOVE item(var0:) TO part
72+
MOVE item(var1:) TO part
73+
MOVE item(2:var0) TO part
74+
MOVE item(2:var1) TO part
75+
76+
* OK Expressions are not checked
77+
MOVE item(2 * 3 : 4 ) TO part
78+
MOVE item(2 : 4 * 2 ) TO part
79+
MOVE item(2 * 2 : 4 * 2 ) TO part
80+
MOVE item(-2 + 1 : 2 ) TO part
81+
MOVE item(2 : 4 * -2) TO part
82+
.
83+
END PROGRAM Pgm.

TypeCobol/Compiler/Diagnostics/CodeElementCheckers.cs

Lines changed: 47 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -407,6 +407,53 @@ public static void OnCodeElement(StopStatement statement, CodeElementsParser.Sto
407407
}
408408
}
409409

410+
internal static class ReferenceModifierChecker
411+
{
412+
private static Diagnostic CreateDiagnostic(string message, IParseTree location)
413+
{
414+
var position = ParseTreeUtils.GetFirstToken(location).Position();
415+
return new Diagnostic(MessageCode.SyntaxErrorInParser, position, message);
416+
}
417+
418+
public static void Check(ReferenceModifier referenceModifier, CodeElementsParser.ReferenceModifierContext context)
419+
{
420+
if (referenceModifier.LeftmostCharacterPosition == null)
421+
{
422+
context.AttachDiagnostic(CreateDiagnostic("Left-most position of a reference modifier is required.", context));
423+
}
424+
else
425+
{
426+
ValidateModifierValue(referenceModifier.LeftmostCharacterPosition);
427+
}
428+
429+
if (referenceModifier.Length != null)
430+
{
431+
ValidateModifierValue(referenceModifier.Length);
432+
}
433+
434+
void ValidateModifierValue(ArithmeticExpression arithmeticExpression)
435+
{
436+
switch (arithmeticExpression.NodeType)
437+
{
438+
case ExpressionNodeType.ArithmeticOperation:
439+
// Cannot do anything in that case
440+
break;
441+
case ExpressionNodeType.NumericVariable:
442+
var numericVariableOperand = (NumericVariableOperand)arithmeticExpression;
443+
var numericVariable = numericVariableOperand.NumericVariable;
444+
// Only negative literals are erroneous
445+
if (numericVariable?.Value?.Value <= 0)
446+
{
447+
context.AttachDiagnostic(CreateDiagnostic("Reference modifiers should be positive non-zero values.", context));
448+
}
449+
break;
450+
default:
451+
throw new InvalidOperationException("Unexpected expression type: " + arithmeticExpression.NodeType);
452+
}
453+
}
454+
}
455+
}
456+
410457
/// <summary>
411458
/// Create diagnostics for language level restricted elements used in a lower level parsing context
412459
/// (typically TypeCobol syntax used in Cobol85 code).

TypeCobol/Compiler/Parser/CodeElementBuilder/CobolExpressionsBuilder.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -469,7 +469,9 @@ private ReferenceModifier CreateReferenceModifier(CodeElementsParser.ReferenceMo
469469
{
470470
length = CreateArithmeticExpression(context.length);
471471
}
472-
return new ReferenceModifier(leftmostCharacterPosition, length);
472+
var referenceModifier = new ReferenceModifier(leftmostCharacterPosition, length);
473+
ReferenceModifierChecker.Check(referenceModifier, context);
474+
return referenceModifier;
473475
}
474476

475477
internal StorageArea CreateIdentifierOrIndexName(CodeElementsParser.IdentifierOrIndexNameContext context)

0 commit comments

Comments
 (0)