Skip to content

Commit

Permalink
Allow for missing nesting levels. Fixes #164.
Browse files Browse the repository at this point in the history
  • Loading branch information
tr11 committed Aug 19, 2019
1 parent 3b768d2 commit 8d39e75
Show file tree
Hide file tree
Showing 3 changed files with 32 additions and 5 deletions.
1 change: 1 addition & 0 deletions .gitignore
Expand Up @@ -48,3 +48,4 @@ dependency-reduced-pom.xml

_testOutput
output
.attach_pid*
Expand Up @@ -194,14 +194,20 @@ class ParserVisitor(enc: Encoding,
levels.pop
}

if (levels.top.children.isEmpty) {
val newTop = levels.top.copy(children = Some(section))
def addLevel(s: Int) = {
val newTop = levels.top.copy(children = Some(s))
levels.pop
levels.push(newTop)
}
if (!levels.top.children.contains(section))
throw new SyntaxErrorException(levels.top.el.children.last.lineNumber, levels.top.el.name,
s"The field is a leaf element and cannot contain nested fields.")

levels.top.children match {
case Some(s) if s == section => { }
case None => addLevel(section)
case Some(s) if s > section => addLevel(section)
case _ =>
throw new SyntaxErrorException(levels.top.el.children.last.lineNumber, levels.top.el.children.last.name,
s"The field is a leaf element and cannot contain nested fields.")
}

levels.top.el
}
Expand Down
Expand Up @@ -19,6 +19,7 @@ package za.co.absa.cobrix.cobol.parser.copybooks
import org.scalatest.FunSuite
import org.slf4j.LoggerFactory
import za.co.absa.cobrix.cobol.parser.CopybookParser
import za.co.absa.cobrix.cobol.parser.exceptions.SyntaxErrorException

class ParseFieldsNestingSpec extends FunSuite {

Expand Down Expand Up @@ -53,4 +54,23 @@ class ParseFieldsNestingSpec extends FunSuite {

assert(layout == expectedLayout)
}

test("Test copybook parser doesn't allow nesting leaf statements") {
val copybookWithCommentLines =
"""
01 ROOT-GROUP.
03 NESTED-PRIMITIVE-01 PIC 9(7) COMP-3.
03 NESTED-GRP-01.
05 NESTED-NESTED-02 PIC X(7).
03 FILL PIC X(07).
02 FILLER_1 PIC XX.
03 NUMERIC-FIELD-01 PIC S9(04) COMP.
"""

val syntaxErrorException = intercept[SyntaxErrorException] {
CopybookParser.parseTree(copybookWithCommentLines)
}
assert(syntaxErrorException.lineNumber == 7)
assert(syntaxErrorException.msg.contains("The field is a leaf element and cannot contain nested fields."))
}
}

0 comments on commit 8d39e75

Please sign in to comment.