Skip to content

Commit 08758b9

Browse files
authored
Merge branch 'develop' into 1816_NewExecutionStep_QualityCheck
2 parents c37090f + 8fd294c commit 08758b9

File tree

7 files changed

+82
-34
lines changed

7 files changed

+82
-34
lines changed
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
EXEC SQL DECLARE Table2 TABLE
2+
( Table2_Field2 CHAR(1) NOT NULL,
3+
) END-EXEC.
4+
01 table2-field2 PIC X.
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
EXEC SQL DECLARE Table2 TABLE
2+
( Table2_Field2 CHAR(1) NOT NULL,
3+
) END-EXEC.
4+
05 table2-field2 PIC X.
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
EXEC SQL DECLARE Table2 TABLE
2+
( Table2_Field2 CHAR(1) NOT NULL,
3+
) END-EXEC.
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
IDENTIFICATION DIVISION.
2+
PROGRAM-ID. DVZZMFT3.
3+
DATA DIVISION.
4+
WORKING-STORAGE SECTION.
5+
*KO empty group item
6+
01 group1.
7+
EXEC SQL DECLARE Table1 TABLE
8+
( Table1_Field1 CHAR(1) NOT NULL,
9+
) END-EXEC.
10+
*KO same thing but with a copy
11+
01 group2.
12+
COPY CopyWithExecSqlOnly.
13+
*KO level number mismatch
14+
01 group3.
15+
COPY CopyWithExecSqlAndData1.
16+
*OK
17+
01 group4.
18+
COPY CopyWithExecSqlAndData2.
19+
PROCEDURE DIVISION.
20+
GOBACK
21+
.
22+
END PROGRAM DVZZMFT3.
Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
 IDENTIFICATION DIVISION.
2+
PROGRAM-ID. DVZZMFT3.
3+
DATA DIVISION.
4+
WORKING-STORAGE SECTION.
5+
*KO empty group item
6+
Line 6[11,16] <27, Error, Syntax> - Syntax error : A group item cannot be empty.
7+
01 group1.
8+
EXEC SQL DECLARE Table1 TABLE
9+
( Table1_Field1 CHAR(1) NOT NULL,
10+
) END-EXEC.
11+
*KO same thing but with a copy
12+
Line 11[11,16] <27, Error, Syntax> - Syntax error : A group item cannot be empty.
13+
01 group2.
14+
COPY CopyWithExecSqlOnly.
15+
*KO level number mismatch
16+
Line 14[11,16] <27, Error, Syntax> - Syntax error : Cannot include copy CopyWithExecSqlAndData1 under level 1 because copy starts at level 1.
17+
01 group3.
18+
COPY CopyWithExecSqlAndData1.
19+
*OK
20+
01 group4.
21+
COPY CopyWithExecSqlAndData2.
22+
PROCEDURE DIVISION.
23+
GOBACK
24+
.
25+
END PROGRAM DVZZMFT3.

TypeCobol/Compiler/CupParser/NodeBuilder/ProgramClassBuilder.cs

Lines changed: 18 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -873,32 +873,39 @@ public virtual void CheckStartSentenceLastStatement()
873873

874874
public virtual void StartExecStatement(ExecStatement execStmt)
875875
{
876-
ExitLastLevel1Definition();
877876
Enter(new Exec(execStmt), execStmt);
878877
Dispatcher.StartExecStatement(execStmt);
879878
}
880879

881880
public virtual void EndExecStatement()
882881
{
883-
//Code duplicated in OnExecStatement
884882
//EndExecStatement (therefore StartExecStatement) is fired if the exec is in a procedure division and is the first instruction
885883
//OnExecStatement is fired if the exec is in a procedure division and is not the first instruction
884+
ExitExecStatement();
885+
Dispatcher.EndExecStatement();
886+
}
886887

887-
//Code to generate a specific ProcedureDeclaration as Nested when an Exec Statement is spotted. See Issue #1209
888-
//This might be helpful for later
889-
//if (_ProcedureDeclaration != null)
890-
//{
891-
// _ProcedureDeclaration.SetFlag(Node.Flag.GenerateAsNested, true);
892-
//}
893-
888+
private void ExitExecStatement()
889+
{
894890
//Code to generate all ProcedureDeclarations as Nested when an Exec Statement is spotted. See Issue #1209
895891
//This is the selected solution until we determine the more optimal way to generate a program that contains Exec Statements
896892
if (_ProcedureDeclaration != null)
897893
{
898894
CurrentNode.Root.MainProgram.SetFlag(Node.Flag.GenerateAsNested, true);
899895
}
896+
897+
var exec = CurrentNode;
900898
Exit();
901-
Dispatcher.EndExecStatement();
899+
900+
//EXECs inside a DataDefinition are moved to the parent data division section
901+
//Children of a DataDefinition are thus guaranteed to be DataDefinition themselves
902+
var targetParent = CurrentNode;
903+
while (targetParent is DataDefinition)
904+
{
905+
targetParent = targetParent.Parent;
906+
}
907+
exec.Parent.Remove(exec);
908+
targetParent.Add(exec);
902909
}
903910

904911
public virtual void OnContinueStatement(ContinueStatement stmt)
@@ -1080,25 +1087,9 @@ public virtual void OnProcedureStyleCall(ProcedureStyleCallStatement stmt, CallS
10801087
public virtual void OnExecStatement(ExecStatement stmt)
10811088
{
10821089
Enter(new Exec(stmt), stmt);
1083-
1084-
//Code duplicated in OnExecStatement
10851090
//EndExecStatement (therefore StartExecStatement) is fired if the exec is in a procedure division and is the first instruction
10861091
//OnExecStatement is fired if the exec is in a procedure division and is not the first instruction
1087-
1088-
//Code to generate a specific ProcedureDeclaration as Nested when an Exec Statement is spotted. See Issue #1209
1089-
//This might be helpful for later
1090-
//if (_ProcedureDeclaration != null)
1091-
//{
1092-
// _ProcedureDeclaration.SetFlag(Node.Flag.GenerateAsNested, true);
1093-
//}
1094-
1095-
//Code to generate all ProcedureDeclarations as Nested when an Exec Statement is spotted. See Issue #1209
1096-
//This is the selected solution until we determine the more optimal way to generate a program that contains Exec Statements
1097-
if (_ProcedureDeclaration != null)
1098-
{
1099-
CurrentNode.Root.MainProgram.SetFlag(Node.Flag.GenerateAsNested, true);
1100-
}
1101-
Exit();
1092+
ExitExecStatement();
11021093
Dispatcher.OnExecStatement(stmt);
11031094
}
11041095

TypeCobol/Compiler/Diagnostics/CrossChecker.cs

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -489,18 +489,17 @@ public override bool Visit(DataDescription dataDescription)
489489
var nodeIndex = dataDescription.Parent.IndexOf(dataDescription);
490490
//Get sibling nodes
491491
var siblingNodes = dataDescription.Parent.Children;
492-
//Check if next node is inside a copy when this isn't the last node
493-
if (siblingNodes.Count > nodeIndex + 1 && siblingNodes[nodeIndex + 1].IsInsideCopy())
492+
//Get immediately following DataDefinition
493+
var nextData = siblingNodes.Skip(nodeIndex + 1).OfType<DataDefinition>().FirstOrDefault();
494+
if (nextData != null && nextData.IsInsideCopy())
494495
{
495-
//Get next sibling node
496-
var nextSibling = siblingNodes[nodeIndex + 1];
497-
DiagnosticUtils.AddError(dataDescription, $"Cannot include copy {nextSibling.CodeElement?.FirstCopyDirective.TextName} " +
496+
DiagnosticUtils.AddError(dataDescription, $"Cannot include copy {nextData.CodeElement.FirstCopyDirective.TextName} " +
498497
$"under level {dataDescriptionEntry.LevelNumber} " +
499-
$"because copy starts at level {((DataDescription)nextSibling).CodeElement.LevelNumber}.", dataDescriptionEntry);
498+
$"because copy starts at level {nextData.CodeElement.LevelNumber}.", dataDescriptionEntry);
500499
}
501-
//Last node so this is an empty group item
502500
else
503501
{
502+
//Last node so this is an empty group item
504503
DiagnosticUtils.AddError(dataDescription, "A group item cannot be empty.", dataDescriptionEntry);
505504
}
506505
}

0 commit comments

Comments
 (0)