Skip to content
Merged
Show file tree
Hide file tree
Changes from 4 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions TypeCobol.Test/Parser/CodeElements/SEARCH.cbl
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@ SEARCH x VARYING y
SEARCH ALL x VARYING y
* ERROR p409: identifier-1 must not be subscripted or reference-modified.
SEARCH identifier1 (ALL)
SEARCH identifier1 (0:1)
SEARCH identifier1 (ALL)(0:1)
SEARCH identifier1 (1:1)
SEARCH identifier1 (ALL)(1:1)
* explicit scope
SEARCH ALL someIdentifier
AT END
Expand Down
64 changes: 64 additions & 0 deletions TypeCobol.Test/Parser/Programs/Cobol85/ReferenceModifiers.rdz.cbl
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
 IDENTIFICATION DIVISION.
PROGRAM-ID. Pgm.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 item PIC X(20).
01 part PIC X(20).
01 var0 PIC 9 VALUE 0.
01 var1 PIC 9 VALUE 1.

PROCEDURE DIVISION.
* OK this is a shorthand
MOVE item(2:) TO part
* KO zero position
MOVE item(0:) TO part
* KO negative position
MOVE item(-1:) TO part
* KO by a previous step
MOVE item(:2) TO part

* KO zero position
MOVE item(0:5) TO part
* KO zero length
MOVE item(1:0) TO part
* KO*2 zero values
MOVE item(0:0) TO part
* KO negative position
MOVE item(-1:5) TO part
* KO negative length
MOVE item(1:-5) TO part
* KO*2 negative values
MOVE item(-1:-5) TO part
* OK
MOVE item(1.32:5) TO part
* OK
MOVE item(1:5.84) TO part
* OK
MOVE item(1.32:5.84) TO part
* KO zero position
MOVE item(0.0:5) TO part
* KO zero length
MOVE item(1:0.0) TO part
* KO*2 zero values
MOVE item(0.0:0.0) TO part
* KO negative position
MOVE item(-1.32:5) TO part
* KO negative length
MOVE item(1:-5.84) TO part
* KO*2 negative values
MOVE item(-1.32:-5.84) TO part

* OK Variables are not checked
MOVE item(var0:) TO part
MOVE item(var1:) TO part
MOVE item(2:var0) TO part
MOVE item(2:var1) TO part

* OK Expressions are not checked
MOVE item(2 * 3 : 4 ) TO part
MOVE item(2 : 4 * 2 ) TO part
MOVE item(2 * 2 : 4 * 2 ) TO part
MOVE item(-2 + 1 : 2 ) TO part
MOVE item(2 : 4 * -2) TO part
.
END PROGRAM Pgm.
Original file line number Diff line number Diff line change
@@ -0,0 +1,83 @@
 IDENTIFICATION DIVISION.
PROGRAM-ID. Pgm.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 item PIC X(20).
01 part PIC X(20).
01 var0 PIC 9 VALUE 0.
01 var1 PIC 9 VALUE 1.

PROCEDURE DIVISION.
* OK this is a shorthand
MOVE item(2:) TO part
* KO zero position
Line 14[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(0:) TO part
* KO negative position
Line 16[22,23] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(-1:) TO part
* KO by a previous step
Line 18[21,21] <27, Error, Syntax> - Syntax error : mismatched input '(' expecting TO
MOVE item(:2) TO part

* KO zero position
Line 21[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(0:5) TO part
* KO zero length
Line 23[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(1:0) TO part
* KO*2 zero values
Line 25[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
Line 25[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(0:0) TO part
* KO negative position
Line 27[22,23] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(-1:5) TO part
* KO negative length
Line 29[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(1:-5) TO part
* KO*2 negative values
Line 31[22,23] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
Line 31[22,23] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(-1:-5) TO part
* OK
MOVE item(1.32:5) TO part
* OK
MOVE item(1:5.84) TO part
* OK
MOVE item(1.32:5.84) TO part
* KO zero position
Line 39[22,24] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(0.0:5) TO part
* KO zero length
Line 41[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(1:0.0) TO part
* KO*2 zero values
Line 43[22,24] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
Line 43[22,24] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(0.0:0.0) TO part
* KO negative position
Line 45[22,26] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(-1.32:5) TO part
* KO negative length
Line 47[22,22] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(1:-5.84) TO part
* KO*2 negative values
Line 49[22,26] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
Line 49[22,26] <27, Error, Syntax> - Syntax error : Reference modifiers should be positive non-zero values.
MOVE item(-1.32:-5.84) TO part

* OK Variables are not checked
MOVE item(var0:) TO part
MOVE item(var1:) TO part
MOVE item(2:var0) TO part
MOVE item(2:var1) TO part

* OK Expressions are not checked
MOVE item(2 * 3 : 4 ) TO part
MOVE item(2 : 4 * 2 ) TO part
MOVE item(2 * 2 : 4 * 2 ) TO part
MOVE item(-2 + 1 : 2 ) TO part
MOVE item(2 : 4 * -2) TO part
.
END PROGRAM Pgm.
47 changes: 47 additions & 0 deletions TypeCobol/Compiler/Diagnostics/CodeElementCheckers.cs
Original file line number Diff line number Diff line change
Expand Up @@ -407,6 +407,53 @@ public static void OnCodeElement(StopStatement statement, CodeElementsParser.Sto
}
}

internal static class ReferenceModifierChecker
{
private static Diagnostic CreateDiagnostic(string message, IParseTree location)
{
var position = ParseTreeUtils.GetFirstToken(location).Position();
return new Diagnostic(MessageCode.SyntaxErrorInParser, position, message);
}

public static void Check(ReferenceModifier referenceModifier, CodeElementsParser.ReferenceModifierContext context)
{
if (referenceModifier.LeftmostCharacterPosition == null)
{
context.AttachDiagnostic(CreateDiagnostic("Left-most position of a reference modifier is required.", context));
}
else
{
ValidateModifierValue(referenceModifier.LeftmostCharacterPosition);
}

if (referenceModifier.Length != null)
{
ValidateModifierValue(referenceModifier.Length);
}

void ValidateModifierValue(ArithmeticExpression arithmeticExpression)
{
switch (arithmeticExpression.NodeType)
{
case ExpressionNodeType.ArithmeticOperation:
// Cannot do anything in that case
break;
case ExpressionNodeType.NumericVariable:
var numericVariableOperand = (NumericVariableOperand)arithmeticExpression;
var numericVariable = numericVariableOperand.NumericVariable;
// Only negative literals are erroneous
if (numericVariable?.Value?.Value <= 0)
{
context.AttachDiagnostic(CreateDiagnostic("Reference modifiers should be positive non-zero values.", context));
}
break;
default:
throw new InvalidOperationException("Unexpected expression type: " + arithmeticExpression.NodeType);
}
}
}
}

/// <summary>
/// Create diagnostics for language level restricted elements used in a lower level parsing context
/// (typically TypeCobol syntax used in Cobol85 code).
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -469,7 +469,9 @@ private ReferenceModifier CreateReferenceModifier(CodeElementsParser.ReferenceMo
{
length = CreateArithmeticExpression(context.length);
}
return new ReferenceModifier(leftmostCharacterPosition, length);
var referenceModifier = new ReferenceModifier(leftmostCharacterPosition, length);
ReferenceModifierChecker.Check(referenceModifier, context);
return referenceModifier;
}

internal StorageArea CreateIdentifierOrIndexName(CodeElementsParser.IdentifierOrIndexNameContext context)
Expand Down