diff --git a/README.md b/README.md
index e4f7b9de..685bb4ee 100644
--- a/README.md
+++ b/README.md
@@ -1686,7 +1686,7 @@ The writer is still in its early stages and has several limitations:
```
- Supported types:
- `PIC X(n)` alphanumeric.
- - `PIC S9(n)` numeric (integral and decimal) with `COMP`/`COMP-4`/`COMP-5` (big-endian), `COMP-3`, and
+ - `PIC S9(n)` numeric (integral and decimal) with `DISPLAY`, `COMP`/`COMP-4`/`COMP-5` (big-endian), `COMP-3`, and
`COMP-9` (Cobrix little-endian).
- Only fixed record length output is supported (`record_format = F`).
- `REDEFINES` and `OCCURS` are not supported.
diff --git a/cobol-parser/src/main/scala/za/co/absa/cobrix/cobol/parser/encoding/DisplayEncoders.scala b/cobol-parser/src/main/scala/za/co/absa/cobrix/cobol/parser/encoding/DisplayEncoders.scala
new file mode 100644
index 00000000..0404dc81
--- /dev/null
+++ b/cobol-parser/src/main/scala/za/co/absa/cobrix/cobol/parser/encoding/DisplayEncoders.scala
@@ -0,0 +1,212 @@
+/*
+ * Copyright 2018 ABSA Group Limited
+ *
+ * Licensed under the Apache License, Version 2.0 (the "License");
+ * you may not use this file except in compliance with the License.
+ * You may obtain a copy of the License at
+ *
+ * http://www.apache.org/licenses/LICENSE-2.0
+ *
+ * Unless required by applicable law or agreed to in writing, software
+ * distributed under the License is distributed on an "AS IS" BASIS,
+ * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+ * See the License for the specific language governing permissions and
+ * limitations under the License.
+ */
+
+package za.co.absa.cobrix.cobol.parser.encoding
+
+import za.co.absa.cobrix.cobol.parser.position.Position
+
+import java.math.RoundingMode
+
+object DisplayEncoders {
+ def encodeDisplayNumberSignSeparate(number: java.math.BigDecimal,
+ signPosition: Option[Position],
+ outputSize: Int,
+ precision: Int,
+ scale: Int,
+ scaleFactor: Int,
+ explicitDecimalPoint: Boolean): Array[Byte] = {
+ val isSigned = signPosition.isDefined
+ val lengthAdjustment = if (isSigned) 1 else 0
+ val isSignPositionRight = signPosition.contains(za.co.absa.cobrix.cobol.parser.position.Right)
+ val bytes = new Array[Byte](outputSize)
+
+ if (number == null || precision < 1 || scale < 0 || outputSize < 1 || (scaleFactor > 0 && scale > 0))
+ return bytes
+
+ val isNegative = number.signum() < 0
+
+ val num = if (explicitDecimalPoint) {
+ val shift = scaleFactor
+
+ val bigDecimal = if (shift == 0)
+ number.abs().setScale(scale, RoundingMode.HALF_EVEN)
+ else
+ number.abs().movePointLeft(shift).setScale(scale, RoundingMode.HALF_EVEN)
+
+ val bigDecimalValue1 = bigDecimal.toPlainString
+
+ val bigDecimalValue = if (bigDecimalValue1.startsWith("0."))
+ bigDecimalValue1.drop(1)
+ else
+ bigDecimalValue1
+
+ val bigDecimalValueLen = bigDecimalValue.length + lengthAdjustment
+
+ if (bigDecimalValueLen > outputSize || (!isSigned && isNegative))
+ return bytes
+
+ bigDecimalValue
+ } else {
+ val shift = scaleFactor - scale
+
+ val bigInt = if (shift == 0)
+ number.abs().setScale(0, RoundingMode.HALF_EVEN).toBigIntegerExact
+ else
+ number.abs().movePointLeft(shift).setScale(0, RoundingMode.HALF_EVEN).toBigIntegerExact
+
+ val intValue = bigInt.toString
+ val intValueLen = intValue.length + lengthAdjustment
+
+ if (intValueLen > outputSize || (!isSigned && isNegative))
+ return bytes
+
+ intValue
+ }
+ setPaddedEbcdicNumberWithSignSeparate(num, isSigned, isNegative, isSignPositionRight, bytes)
+ bytes
+ }
+
+ def encodeDisplayNumberSignOverpunched(number: java.math.BigDecimal,
+ signPosition: Option[Position],
+ outputSize: Int,
+ precision: Int,
+ scale: Int,
+ scaleFactor: Int,
+ explicitDecimalPoint: Boolean): Array[Byte] = {
+ val isSigned = signPosition.isDefined
+ val bytes = new Array[Byte](outputSize)
+
+ if (number == null || precision < 1 || scale < 0 || outputSize < 1 || (scaleFactor > 0 && scale > 0))
+ return bytes
+
+ val isNegative = number.signum() < 0
+
+ val num = if (explicitDecimalPoint) {
+ val shift = scaleFactor
+
+ val bigDecimal = if (shift == 0)
+ number.abs().setScale(scale, RoundingMode.HALF_EVEN)
+ else
+ number.abs().movePointLeft(shift).setScale(scale, RoundingMode.HALF_EVEN)
+
+ val bigDecimalValue1 = bigDecimal.toPlainString
+
+ val bigDecimalValue = if (bigDecimalValue1.startsWith("0."))
+ bigDecimalValue1.drop(1)
+ else
+ bigDecimalValue1
+
+ val bigDecimalValueLen = bigDecimalValue.length
+
+ if (bigDecimalValueLen > outputSize || (!isSigned && isNegative))
+ return bytes
+
+ bigDecimalValue
+ } else {
+ val shift = scaleFactor - scale
+
+ val bigInt = if (shift == 0)
+ number.abs().setScale(0, RoundingMode.HALF_EVEN).toBigIntegerExact
+ else
+ number.abs().movePointLeft(shift).setScale(0, RoundingMode.HALF_EVEN).toBigIntegerExact
+
+ val intValue = bigInt.toString
+ val intValueLen = intValue.length
+
+ if (intValueLen > outputSize || (!isSigned && isNegative))
+ return bytes
+
+ intValue
+ }
+ setPaddedEbcdicNumberWithSignOverpunched(num, isSigned, isNegative, bytes)
+ bytes
+ }
+
+ def setPaddedEbcdicNumberWithSignOverpunched(num: String, isSigned: Boolean, isNegative: Boolean, array: Array[Byte]): Unit = {
+ val numLen = num.length
+ val arLen = array.length
+
+ if (numLen > arLen)
+ return
+
+ var i = 0
+ while (i < arLen) {
+ var ebcdic = 0xF0.toByte
+
+ if (i == 0) {
+ // Signal overpunching
+ val c = num(numLen - i - 1)
+ if (c >= '0' && c <= '9') {
+ val digit = c - '0'
+ val zone = if (!isSigned) {
+ 0xF
+ } else if (isNegative) {
+ 0xD
+ } else {
+ 0xC
+ }
+
+ ebcdic = ((zone << 4) | digit).toByte
+ }
+ } else if (i < numLen) {
+ val c = num(numLen - i - 1)
+ if (c >= '0' && c <= '9') {
+ ebcdic = ((c - '0') + 0xF0).toByte
+ } else if (c == '.') {
+ ebcdic = 0x4B
+ }
+ }
+
+ array(arLen - i - 1) = ebcdic
+ i += 1
+ }
+ }
+
+ def setPaddedEbcdicNumberWithSignSeparate(num: String, isSigned: Boolean, isNegative: Boolean, isSignPositionRight: Boolean, array: Array[Byte]): Unit = {
+ val numLen = num.length
+ val arLen = array.length
+ val fullNumLength = if (isSigned) numLen + 1 else numLen
+
+ if (fullNumLength > arLen)
+ return
+
+ val shift = if (isSigned && isSignPositionRight) 1 else 0
+ var i = 0
+ while (i < arLen - shift) {
+ var ebcdic = 0xF0.toByte
+
+ if (i < numLen) {
+ val c = num(numLen - i - 1)
+ if (c >= '0' && c <= '9') {
+ ebcdic = ((c - '0') + 0xF0).toByte
+ } else if (c == '.') {
+ ebcdic = 0x4B
+ }
+ }
+
+ array(arLen - i - shift - 1) = ebcdic
+ i += 1
+ }
+
+ if (isSigned) {
+ if (isNegative) {
+ if (isSignPositionRight) array(arLen - 1) = 0x60 else array(0) = 0x60
+ } else {
+ if (isSignPositionRight) array(arLen - 1) = 0x4E else array(0) = 0x4E
+ }
+ }
+ }
+}
diff --git a/cobol-parser/src/main/scala/za/co/absa/cobrix/cobol/parser/encoding/EncoderSelector.scala b/cobol-parser/src/main/scala/za/co/absa/cobrix/cobol/parser/encoding/EncoderSelector.scala
index 56962c99..ddce9a04 100644
--- a/cobol-parser/src/main/scala/za/co/absa/cobrix/cobol/parser/encoding/EncoderSelector.scala
+++ b/cobol-parser/src/main/scala/za/co/absa/cobrix/cobol/parser/encoding/EncoderSelector.scala
@@ -19,6 +19,7 @@ package za.co.absa.cobrix.cobol.parser.encoding
import za.co.absa.cobrix.cobol.parser.ast.datatype.{AlphaNumeric, COMP3, COMP3U, COMP4, COMP9, CobolType, Decimal, Integral, Usage}
import za.co.absa.cobrix.cobol.parser.decoders.BinaryUtils
import za.co.absa.cobrix.cobol.parser.encoding.codepage.{CodePage, CodePageCommon}
+import za.co.absa.cobrix.cobol.parser.position.Position
import java.nio.charset.{Charset, StandardCharsets}
import java.util
@@ -48,6 +49,10 @@ object EncoderSelector {
Option(getBinaryEncoder(decimalBinary.compact, decimalBinary.precision, decimalBinary.scale, decimalBinary.scaleFactor, decimalBinary.signPosition.isDefined, isBigEndian = true))
case decimalBinary: Decimal if decimalBinary.compact.exists(_.isInstanceOf[COMP9]) =>
Option(getBinaryEncoder(decimalBinary.compact, decimalBinary.precision, decimalBinary.scale, decimalBinary.scaleFactor, decimalBinary.signPosition.isDefined, isBigEndian = false))
+ case integralDisplay: Integral if integralDisplay.compact.isEmpty =>
+ Option(getDisplayEncoder(integralDisplay.precision, 0, 0, integralDisplay.signPosition, isExplicitDecimalPt = false, isSignSeparate = integralDisplay.isSignSeparate))
+ case decimalDisplay: Decimal if decimalDisplay.compact.isEmpty =>
+ Option(getDisplayEncoder(decimalDisplay.precision, decimalDisplay.scale, decimalDisplay.scaleFactor, decimalDisplay.signPosition, decimalDisplay.explicitDecimal, decimalDisplay.isSignSeparate))
case _ =>
None
}
@@ -140,4 +145,30 @@ object EncoderSelector {
}
}
+ def getDisplayEncoder(precision: Int,
+ scale: Int,
+ scaleFactor: Int,
+ signPosition: Option[Position],
+ isExplicitDecimalPt: Boolean,
+ isSignSeparate: Boolean): Encoder = {
+ val isSigned = signPosition.isDefined
+ val numBytes = BinaryUtils.getBytesCount(None, precision, isSigned, isExplicitDecimalPt = isExplicitDecimalPt, isSignSeparate = isSignSeparate)
+ (a: Any) => {
+ val number = a match {
+ case null => null
+ case d: java.math.BigDecimal => d
+ case n: java.math.BigInteger => new java.math.BigDecimal(n)
+ case n: Byte => new java.math.BigDecimal(n)
+ case n: Int => new java.math.BigDecimal(n)
+ case n: Long => new java.math.BigDecimal(n)
+ case x => new java.math.BigDecimal(x.toString)
+ }
+ if (isSignSeparate) {
+ DisplayEncoders.encodeDisplayNumberSignSeparate(number, signPosition, numBytes, precision, scale, scaleFactor, explicitDecimalPoint = isExplicitDecimalPt)
+ } else {
+ DisplayEncoders.encodeDisplayNumberSignOverpunched(number, signPosition, numBytes, precision, scale, scaleFactor, explicitDecimalPoint = isExplicitDecimalPt)
+ }
+ }
+ }
+
}
diff --git a/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/BCDNumberEncodersSuite.scala b/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/BCDNumberEncodersSuite.scala
index e3331d48..67905be0 100644
--- a/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/BCDNumberEncodersSuite.scala
+++ b/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/BCDNumberEncodersSuite.scala
@@ -17,11 +17,19 @@
package za.co.absa.cobrix.cobol.parser.encoding
import org.scalatest.wordspec.AnyWordSpec
+import za.co.absa.cobrix.cobol.parser.position.Left
import za.co.absa.cobrix.cobol.testutils.ComparisonUtils._
class BCDNumberEncodersSuite extends AnyWordSpec {
"encodeBCDNumber" should {
"integral number" when {
+ "encode a null" in {
+ val expected = Array(0x00, 0x00).map(_.toByte)
+ val actual = BCDNumberEncoders.encodeBCDNumber(null: java.math.BigDecimal, 2, 0, 0, signed = true, mandatorySignNibble = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
"encode a number" in {
val expected = Array[Byte](0x12, 0x34, 0x5C)
val actual = BCDNumberEncoders.encodeBCDNumber(new java.math.BigDecimal(12345), 5, 0, 0, signed = true, mandatorySignNibble = true)
@@ -133,6 +141,13 @@ class BCDNumberEncodersSuite extends AnyWordSpec {
}
"decimal number" when {
+ "encode a null" in {
+ val expected = Array(0x00, 0x00).map(_.toByte)
+ val actual = BCDNumberEncoders.encodeBCDNumber(null: java.math.BigDecimal, 2, 1, 0, signed = true, mandatorySignNibble = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
"encode a number" in {
val expected = Array[Byte](0x12, 0x34, 0x5C)
val actual = BCDNumberEncoders.encodeBCDNumber(java.math.BigDecimal.valueOf(123.45), 5, 2, 0, signed = true, mandatorySignNibble = true)
diff --git a/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/BinaryEncodersSuite.scala b/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/BinaryEncodersSuite.scala
index cbf12745..5e7894a1 100644
--- a/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/BinaryEncodersSuite.scala
+++ b/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/BinaryEncodersSuite.scala
@@ -21,6 +21,13 @@ import za.co.absa.cobrix.cobol.testutils.ComparisonUtils._
class BinaryEncodersSuite extends AnyWordSpec {
"encodeBinaryNumber" should {
+ "encode a null" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = BinaryEncoders.encodeBinaryNumber(null: java.math.BigDecimal, isSigned = true, outputSize = 4, bigEndian = true, precision = 5, scale = 0, scaleFactor = 0)
+
+ assertArraysEqual(actual, expected)
+ }
+
"encode a positive integer in big-endian format" in {
val expected = Array(0x00, 0x00, 0x30, 0x39).map(_.toByte) // 12345 in hex
val actual = BinaryEncoders.encodeBinaryNumber(new java.math.BigDecimal(12345), isSigned = true, outputSize = 4, bigEndian = true, precision = 5, scale = 0, scaleFactor = 0)
diff --git a/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/DisplayEncodersSuite.scala b/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/DisplayEncodersSuite.scala
new file mode 100644
index 00000000..359458a2
--- /dev/null
+++ b/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/parser/encoding/DisplayEncodersSuite.scala
@@ -0,0 +1,641 @@
+/*
+ * Copyright 2018 ABSA Group Limited
+ *
+ * Licensed under the Apache License, Version 2.0 (the "License");
+ * you may not use this file except in compliance with the License.
+ * You may obtain a copy of the License at
+ *
+ * http://www.apache.org/licenses/LICENSE-2.0
+ *
+ * Unless required by applicable law or agreed to in writing, software
+ * distributed under the License is distributed on an "AS IS" BASIS,
+ * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+ * See the License for the specific language governing permissions and
+ * limitations under the License.
+ */
+
+package za.co.absa.cobrix.cobol.parser.encoding
+
+import org.scalatest.wordspec.AnyWordSpec
+import za.co.absa.cobrix.cobol.parser.position._
+import za.co.absa.cobrix.cobol.testutils.ComparisonUtils.assertArraysEqual
+
+class DisplayEncodersSuite extends AnyWordSpec {
+ "encodeDisplayNumberSignOverpunched" should {
+ "integral number" when {
+ "encode a null" in {
+ val expected = Array(0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(null: java.math.BigDecimal, signPosition = Some(Left), 3, 2, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0xF4, 0xC5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(12345), signPosition = Some(Left), 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with an even precision" in {
+ val expected = Array(0xF1, 0xF2, 0xF3, 0xC4).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(1234), signPosition = Some(Left), 4, 4, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0xF0, 0xF0, 0xC5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(5), signPosition = Some(Left), 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode an unsigned number" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0xF4, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(12345), signPosition = None, 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a negative number" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0xF4, 0xD5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-12345), signPosition = Some(Left), 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small negative number" in {
+ val expected = Array( 0xF0, 0xF0, 0xF0, 0xF0, 0xD7).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-7), signPosition = Some(Right), 5, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big number" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(123456), signPosition = Some(Left), 5, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big negative number" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-123456), signPosition = Some(Left), 5, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with negative scale" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(12345), signPosition = Some(Left), 6, 5, -1, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "attempt to encode a signed number when unsigned is expected" in {
+ val expected = Array[Byte](0x00, 0x00, 0x00, 0x00, 0x00, 0x00)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-12345), signPosition = None, 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "attempt to encode a number with an incorrect precision" in {
+ val expected = Array[Byte](0x00, 0x00, 0x00, 0x00)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(12345), signPosition = None, 4, 4, 0, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "attempt to encode a number with zero precision" in {
+ val expected = Array[Byte](0x00)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(12345), signPosition = None, 1, 0, 0, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+ }
+
+ "decimal number" when {
+ "encode a null" in {
+ val expected = Array(0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(null: java.math.BigDecimal, signPosition = Some(Left), 3, 2, 1, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a null and separate decimal point" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(null: java.math.BigDecimal, signPosition = Some(Left), 4, 2, 1, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0xF4, 0xC5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(123.45), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with explicit decimal" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0x4B, 0xF4, 0xC5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(123.45), signPosition = Some(Left), 7, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 1" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0xF0, 0xF0, 0xC5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(0.05), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 2" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0xF0, 0xF5, 0xC0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(0.5), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 3" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0xF0, 0xF0, 0xC1).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(0.005), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 1 with explicit decimal point" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0x4B, 0xF0, 0xC5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(0.05), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 2 with explicit decimal point" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0x4B, 0xF5, 0xC0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(0.5), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 3 with explicit decimal point" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0x4B, 0xF0, 0xC1).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(0.005), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode an unsigned number" in {
+ val expected = Array(0xF1, 0xF2, 0xF3, 0xF4, 0xF5, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(1234.5), signPosition = None, 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode an unsigned number with explicit decimal point" in {
+ val expected = Array(0xF1, 0xF2, 0xF3, 0xF4, 0x4B, 0xF5, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(1234.5), signPosition = None, 7, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a negative number" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0xF4, 0xD5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-12.345), signPosition = Some(Left), 6, 5, 3, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a negative number with explicit decimal point" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0x4B, 0xF3, 0xF4, 0xD5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-12.345), signPosition = Some(Right), 7, 5, 3, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small negative number" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0xF0, 0xD7).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-0.00007), signPosition = Some(Right), 5, 4, 5, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small negative number with explicit decimal point" in {
+ val expected = Array(0xF0, 0xF0, 0x4B, 0xF0, 0xF0, 0xF0, 0xF0, 0xD7).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-0.00007), signPosition = Some(Left), 8, 4, 5, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too precise number" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0xF4, 0xF6).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(123.456), signPosition = None, 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too precise number with explicit decimal point" in {
+ val expected = Array(0xF1, 0xF2, 0xF3, 0x4B, 0xF4, 0xF6).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(123.456), signPosition = None, 6, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big number" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(1234.56), signPosition = None, 5, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big number with explicit decimal point" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(1234.56), signPosition = None, 6, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big negative number" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-1234.56), signPosition = Some(Right), 5, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big negative number with explicit decimal point" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-1234.56), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with positive scale factor" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0xF1, 0xF2, 0xC3).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(12300), signPosition = Some(Left), 6, 5, 0, 2, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with positive scale factor with explicit decimal point" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(123400), signPosition = Some(Left), 6, 5, 1, 2, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with negative scale factor" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0xF1, 0xF2, 0xC3).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(1.23), signPosition = Some(Left), 6, 5, 0, -2, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with negative scale factor with explicit decimal point" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0x4B, 0xC4).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(1.234), signPosition = Some(Left), 6, 5, 1, -2, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number with negative scale factor" in {
+ val expected = Array(0xF0, 0xF0, 0xF1, 0xF2, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(0.00012), signPosition = None, 5, 4, 3, -3, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number with negative scale factor with explicit decimal point" in {
+ val expected = Array(0x4B, 0xF1, 0xF2, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(0.00012), signPosition = None, 4, 4, 3, -3, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small negative number with negative scale factor with explicit decimal point" in {
+ val expected = Array(0x4B, 0xF1, 0xF2, 0xD0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-0.00012), signPosition = Some(Left), 4, 4, 3, -3, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small negative number with negative scale factor with explicit decimal point and sign from right side" in {
+ val expected = Array(0x4B, 0xF1, 0xF2, 0xD0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignOverpunched(new java.math.BigDecimal(-0.00012), signPosition = Some(Right), 4, 4, 3, -3, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+ }
+ }
+
+
+ "encodeDisplayNumberSignSeparate" should {
+ "integral number" when {
+ "encode a null" in {
+ val expected = Array(0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(null: java.math.BigDecimal, signPosition = Some(Left), 3, 2, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number" in {
+ val expected = Array(0x4E, 0xF1, 0xF2, 0xF3, 0xF4, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(12345), signPosition = Some(Left), 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with an even precision" in {
+ val expected = Array(0x4E, 0xF1, 0xF2, 0xF3, 0xF4).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(1234), signPosition = Some(Left), 5, 4, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number" in {
+ val expected = Array(0x4E, 0xF0, 0xF0, 0xF0, 0xF0, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(5), signPosition = Some(Left), 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode an unsigned number" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0xF4, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(12345), signPosition = None, 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a negative number" in {
+ val expected = Array(0x60, 0xF1, 0xF2, 0xF3, 0xF4, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-12345), signPosition = Some(Left), 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small negative number" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0xF0, 0xF7, 0x60).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-7), signPosition = Some(Right), 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big number" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(123456), signPosition = Some(Left), 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big negative number" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-123456), signPosition = Some(Left), 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with negative scale" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(12345), signPosition = Some(Left), 6, 5, -1, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "attempt to encode a signed number when unsigned is expected" in {
+ val expected = Array[Byte](0x00, 0x00, 0x00, 0x00, 0x00, 0x00)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-12345), signPosition = None, 6, 5, 0, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "attempt to encode a number with an incorrect precision" in {
+ val expected = Array[Byte](0x00, 0x00, 0x00, 0x00, 0x00)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(12345), signPosition = Some(Left), 5, 4, 0, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "attempt to encode a number with zero precision" in {
+ val expected = Array[Byte](0x00)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(12345), signPosition = None, 1, 0, 0, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+ }
+
+ "decimal number" when {
+ "encode a null" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(null: java.math.BigDecimal, signPosition = Some(Left), 4, 2, 1, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a null and separate decimal point" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(null: java.math.BigDecimal, signPosition = Some(Left), 5, 2, 1, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number" in {
+ val expected = Array(0x4E, 0xF1, 0xF2, 0xF3, 0xF4, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(123.45), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with explicit decimal" in {
+ val expected = Array(0x4E, 0xF1, 0xF2, 0xF3, 0x4B, 0xF4, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(123.45), signPosition = Some(Left), 7, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 1" in {
+ val expected = Array(0x4E, 0xF0, 0xF0, 0xF0, 0xF0, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(0.05), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 2" in {
+ val expected = Array(0x4E, 0xF0, 0xF0, 0xF0, 0xF5, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(0.5), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 3" in {
+ val expected = Array(0x4E, 0xF0, 0xF0, 0xF0, 0xF0, 0xF1).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(0.005), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 1 with explicit decimal point" in {
+ val expected = Array(0x4E, 0xF0, 0xF0, 0x4B, 0xF0, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(0.05), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 2 with explicit decimal point" in {
+ val expected = Array(0x4E, 0xF0, 0xF0, 0x4B, 0xF5, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(0.5), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number 3 with explicit decimal point" in {
+ val expected = Array(0x4E, 0xF0, 0xF0, 0x4B, 0xF0, 0xF1).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(0.005), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode an unsigned number" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0xF4, 0xF5, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(1234.5), signPosition = None, 7, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode an unsigned number with explicit decimal point" in {
+ val expected = Array(0xF1, 0xF2, 0xF3, 0xF4, 0x4B, 0xF5, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(1234.5), signPosition = None, 7, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a negative number" in {
+ val expected = Array(0x60, 0xF1, 0xF2, 0xF3, 0xF4, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-12.345), signPosition = Some(Left), 6, 5, 3, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a negative number with explicit decimal point" in {
+ val expected = Array(0x60, 0xF1, 0xF2, 0x4B, 0xF3, 0xF4, 0xF5).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-12.345), signPosition = Some(Left), 7, 5, 3, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small negative number" in {
+ val expected = Array(0xF0, 0xF0, 0xF0, 0xF7, 0x60).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-0.00007), signPosition = Some(Right), 5, 4, 5, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small negative number with explicit decimal point" in {
+ val expected = Array(0x60, 0xF0, 0x4B, 0xF0, 0xF0, 0xF0, 0xF0, 0xF7).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-0.00007), signPosition = Some(Left), 8, 4, 5, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too precise number" in {
+ val expected = Array(0xF0, 0xF1, 0xF2, 0xF3, 0xF4, 0xF6).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(123.456), signPosition = None, 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too precise number with explicit decimal point" in {
+ val expected = Array(0xF1, 0xF2, 0xF3, 0x4B, 0xF4, 0xF6).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(123.456), signPosition = None, 6, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big number" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(1234.56), signPosition = Some(Left), 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big number with explicit decimal point" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(1234.56), signPosition = Some(Left), 7, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big negative number" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-1234.56), signPosition = Some(Right), 6, 5, 2, 0, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a too big negative number with explicit decimal point" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-1234.56), signPosition = Some(Left), 7, 5, 2, 0, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with positive scale factor" in {
+ val expected = Array(0x4E, 0xF0, 0xF0, 0xF1, 0xF2, 0xF3).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(12300), signPosition = Some(Left), 6, 5, 0, 2, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with positive scale factor with explicit decimal point" in {
+ val expected = Array(0x00, 0x00, 0x00, 0x00, 0x00, 0x00).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(123400), signPosition = Some(Left), 6, 5, 1, 2, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with negative scale factor" in {
+ val expected = Array(0x4E, 0xF0, 0xF0, 0xF1, 0xF2, 0xF3).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(1.23), signPosition = Some(Left), 6, 5, 0, -2, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a number with negative scale factor with explicit decimal point" in {
+ val expected = Array(0x4E, 0xF1, 0xF2, 0xF3, 0x4B, 0xF4).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(1.234), signPosition = Some(Left), 6, 5, 1, -2, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number with negative scale factor" in {
+ val expected = Array(0xF0, 0xF0, 0xF1, 0xF2, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(0.00012), signPosition = None, 5, 4, 3, -3, explicitDecimalPoint = false)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small number with negative scale factor with explicit decimal point" in {
+ val expected = Array(0x4B, 0xF1, 0xF2, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(0.00012), signPosition = None, 4, 4, 3, -3, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small negative number with negative scale factor with explicit decimal point" in {
+ val expected = Array(0x60, 0x4B, 0xF1, 0xF2, 0xF0).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-0.00012), signPosition = Some(Left), 5, 4, 3, -3, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ "encode a small negative number with negative scale factor with explicit decimal point and sign from right side" in {
+ val expected = Array(0x4B, 0xF1, 0xF2, 0xF0, 0x60).map(_.toByte)
+ val actual = DisplayEncoders.encodeDisplayNumberSignSeparate(new java.math.BigDecimal(-0.00012), signPosition = Some(Right), 5, 4, 3, -3, explicitDecimalPoint = true)
+
+ assertArraysEqual(actual, expected)
+ }
+
+ }
+ }
+
+
+}
diff --git a/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/testutils/ComparisonUtils.scala b/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/testutils/ComparisonUtils.scala
index 43fd5301..32a59987 100644
--- a/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/testutils/ComparisonUtils.scala
+++ b/cobol-parser/src/test/scala/za/co/absa/cobrix/cobol/testutils/ComparisonUtils.scala
@@ -22,9 +22,9 @@ import org.scalatest.Assertions.{fail, succeed}
object ComparisonUtils {
def assertArraysEqual(actual: Array[Byte], expected: Array[Byte]): Assertion = {
if (!actual.sameElements(expected)) {
- val actualHex = actual.map(b => f"$b%02X").mkString(" ")
- val expectedHex = expected.map(b => f"$b%02X").mkString(" ")
- fail(s"Actual: $actualHex\nExpected: $expectedHex")
+ val actualHex = actual.map(b => f"0x$b%02X").mkString(", ")
+ val expectedHex = expected.map(b => f"0x$b%02X").mkString(", ")
+ fail(s"Actual: $actualHex\nExpected: $expectedHex")
} else {
succeed
}
diff --git a/pom.xml b/pom.xml
index 631e0443..d7edc415 100644
--- a/pom.xml
+++ b/pom.xml
@@ -94,13 +94,11 @@
yyyy-MM-dd'T'HH:mm:ssX
3.10.1
- 1.8
- 1.8
3.2.1
2.3
3.0.1
2.19.1
- 1.0
+ 2.2.0
2.4.2
1.8.1
1.3.0
@@ -110,8 +108,8 @@
2.12.20
2.12
- 3.5.2
- 3.2.14
+ 3.5.6
+ 3.2.19
2.4.16
15.0
2.13.1
diff --git a/project/Dependencies.scala b/project/Dependencies.scala
index a8697936..17a8920d 100644
--- a/project/Dependencies.scala
+++ b/project/Dependencies.scala
@@ -23,12 +23,12 @@ object Dependencies {
private val slf4jVersion = "1.7.25"
private val jacksonVersion = "2.13.0"
- private val scalatestVersion = "3.2.14"
+ private val scalatestVersion = "3.2.19"
private val mockitoVersion = "4.11.0"
private val defaultSparkVersionForScala211 = "2.4.8"
private val defaultSparkVersionForScala212 = "3.4.4"
- private val defaultSparkVersionForScala213 = "3.5.5"
+ private val defaultSparkVersionForScala213 = "3.5.6"
def sparkFallbackVersion(scalaVersion: String): String = {
if (scalaVersion.startsWith("2.11.")) {
@@ -87,7 +87,7 @@ object Dependencies {
val CobolConvertersDependencies: Seq[ModuleID] = Seq(
// compile
- "org.slf4j" % "slf4j-api" % slf4jVersion,
+ "org.slf4j" % "slf4j-api" % slf4jVersion,
"com.fasterxml.jackson.module" %% "jackson-module-scala" % jacksonVersion,
"com.fasterxml.jackson.dataformat" % "jackson-dataformat-xml" % jacksonVersion,
"com.fasterxml.jackson.dataformat" % "jackson-dataformat-csv" % jacksonVersion,
diff --git a/spark-cobol/src/main/scala/za/co/absa/cobrix/spark/cobol/writer/BasicRecordCombiner.scala b/spark-cobol/src/main/scala/za/co/absa/cobrix/spark/cobol/writer/BasicRecordCombiner.scala
index 56fb1c5d..4521d16a 100644
--- a/spark-cobol/src/main/scala/za/co/absa/cobrix/spark/cobol/writer/BasicRecordCombiner.scala
+++ b/spark-cobol/src/main/scala/za/co/absa/cobrix/spark/cobol/writer/BasicRecordCombiner.scala
@@ -31,9 +31,10 @@ class BasicRecordCombiner extends RecordCombiner {
override def combine(df: DataFrame, cobolSchema: CobolSchema, readerParameters: ReaderParameters): RDD[Array[Byte]] = {
val ast = getAst(cobolSchema)
val copybookFields = ast.children.filter {
- case p: Primitive => !p.isFiller
- case g: Group => !g.isFiller
- case _ => true
+ case f if f.redefines.nonEmpty => false
+ case p: Primitive => !p.isFiller
+ case g: Group => !g.isFiller
+ case _ => true
}
validateSchema(df, copybookFields.toSeq)
diff --git a/spark-cobol/src/test/scala/za/co/absa/cobrix/spark/cobol/writer/FixedLengthEbcdicWriterSuite.scala b/spark-cobol/src/test/scala/za/co/absa/cobrix/spark/cobol/writer/FixedLengthEbcdicWriterSuite.scala
index ef425e5b..6e618425 100644
--- a/spark-cobol/src/test/scala/za/co/absa/cobrix/spark/cobol/writer/FixedLengthEbcdicWriterSuite.scala
+++ b/spark-cobol/src/test/scala/za/co/absa/cobrix/spark/cobol/writer/FixedLengthEbcdicWriterSuite.scala
@@ -18,11 +18,13 @@ package za.co.absa.cobrix.spark.cobol.writer
import org.apache.hadoop.fs.Path
import org.apache.spark.sql.SaveMode
+import org.scalatest.Assertion
import org.scalatest.wordspec.AnyWordSpec
import za.co.absa.cobrix.spark.cobol.source.base.SparkTestBase
-import za.co.absa.cobrix.spark.cobol.source.fixtures.BinaryFileFixture
+import za.co.absa.cobrix.spark.cobol.source.fixtures.{BinaryFileFixture, TextComparisonFixture}
+import za.co.absa.cobrix.spark.cobol.utils.SparkUtils
-class FixedLengthEbcdicWriterSuite extends AnyWordSpec with SparkTestBase with BinaryFileFixture {
+class FixedLengthEbcdicWriterSuite extends AnyWordSpec with SparkTestBase with BinaryFileFixture with TextComparisonFixture {
import spark.implicits._
@@ -258,6 +260,123 @@ class FixedLengthEbcdicWriterSuite extends AnyWordSpec with SparkTestBase with B
}
}
+ "write data frames with DISPLAY fields" in {
+ withTempDirectory("cobol_writer1") { tempDir =>
+ val bigDecimalNull = null: java.math.BigDecimal
+ val df = List(
+ (-1, 100.5, new java.math.BigDecimal(10.23), 1, 10050, new java.math.BigDecimal(10.12)),
+ (2, 800.4, new java.math.BigDecimal(30), 2, 80040, new java.math.BigDecimal(30)),
+ (3, 22.33, new java.math.BigDecimal(-20), -3, -2233, new java.math.BigDecimal(-20.456)),
+ (4, -1.0, bigDecimalNull, 400, 1000000, bigDecimalNull)
+ ).toDF("A", "B", "C", "D", "E", "F")
+
+ val path = new Path(tempDir, "writer1")
+
+ val copybookContentsWithDisplayFields =
+ """ 01 RECORD.
+ 05 A PIC S9(1).
+ 05 B PIC 9(4)V9(2).
+ 05 C PIC S9(2).9(2).
+ 05 C1 PIC X(5) REDEFINES C.
+ 05 D PIC 9(1).
+ 05 E PIC S9(6) SIGN IS LEADING SEPARATE.
+ 05 F PIC S9(2).9(2) SIGN IS TRAILING SEPARATE.
+ """
+
+ df.coalesce(1)
+ .orderBy("A")
+ .write
+ .format("cobol")
+ .mode(SaveMode.Overwrite)
+ .option("copybook_contents", copybookContentsWithDisplayFields)
+ .save(path.toString)
+
+ val fs = path.getFileSystem(spark.sparkContext.hadoopConfiguration)
+
+ assert(fs.exists(path), "Output directory should exist")
+ val files = fs.listStatus(path)
+ .filter(_.getPath.getName.startsWith("part-"))
+
+ assert(files.nonEmpty, "Output directory should contain part files")
+
+ val partFile = files.head.getPath
+ val data = fs.open(partFile)
+ val bytes = new Array[Byte](files.head.getLen.toInt)
+ data.readFully(bytes)
+ data.close()
+
+ // Expected EBCDIC data for sample test data
+ val expected = Array(
+ 0xD1, // -1 PIC S9(1).
+ 0xF0, 0xF1, 0xF0, 0xF0, 0xF5, 0xF0, // 100.5 PIC 9(4)V9(2)
+ 0xF1, 0xF0, 0x4B, 0xF2, 0xC3, // 10.23 PIC S9(2).9(2)
+ 0xF1, // 1 9(1)
+ 0x4E, 0xF0, 0xF1, 0xF0, 0xF0, 0xF5, 0xF0, // 10050 S9(6) SIGN IS LEADING SEPARATE.
+ 0xF1, 0xF0, 0x4B, 0xF1, 0xF2, 0x4E, // 10.12 S9(2).9(2) SIGN IS TRAILING SEPARATE
+
+ 0xC2, // 2 PIC S9(1).
+ 0xF0, 0xF8, 0xF0, 0xF0, 0xF4, 0xF0, // 800.4 PIC 9(4)V9(2)
+ 0xF3, 0xF0, 0x4B, 0xF0, 0xC0, // 30 PIC S9(2).9(2)
+ 0xF2, // 2 9(1)
+ 0x4E, 0xF0, 0xF8, 0xF0, 0xF0, 0xF4, 0xF0, // 80040 S9(6) SIGN IS LEADING SEPARATE.
+ 0xF3, 0xF0, 0x4B, 0xF0, 0xF0, 0x4E, // 30 S9(2).9(2) SIGN IS TRAILING SEPARATE
+
+ 0xC3, // 3 PIC S9(1).
+ 0xF0, 0xF0, 0xF2, 0xF2, 0xF3, 0xF3, // 22.33 PIC 9(4)V9(2)
+ 0xF2, 0xF0, 0x4B, 0xF0, 0xD0, // -20 PIC S9(2).9(2)
+ 0x00, // null PIC 9(1) (because a negative value cannot be converted to this PIC)
+ 0x60, 0xF0, 0xF0, 0xF2, 0xF2, 0xF3, 0xF3, // -2233 S9(6) SIGN IS LEADING SEPARATE.
+ 0xF2, 0xF0, 0x4B, 0xF4, 0xF6, 0x60, // -20 S9(2).9(2) SIGN IS TRAILING SEPARATE
+
+ 0xC4, // 4 PIC S9(1).
+ 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, // nulls
+ 0x00, 0x00, 0x00, 0x00, 0x00,
+ 0x00,
+ 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00,
+ 0x00, 0x00, 0x00, 0x00, 0x00, 0x00
+ ).map(_.toByte)
+
+ assertArraysEqual(bytes, expected)
+
+ val df2 = spark.read.format("cobol")
+ .option("copybook_contents", copybookContentsWithDisplayFields)
+ .load(path.toString)
+ .orderBy("A")
+
+ val expectedJson =
+ """[ {
+ | "A" : -1,
+ | "B" : 100.5,
+ | "C" : 10.23,
+ | "C1" : "10.2C",
+ | "D" : 1,
+ | "E" : 10050,
+ | "F" : 10.12
+ |}, {
+ | "A" : 2,
+ | "B" : 800.4,
+ | "C" : 30.0,
+ | "C1" : "30.0{",
+ | "D" : 2,
+ | "E" : 80040,
+ | "F" : 30.0
+ |}, {
+ | "A" : 3,
+ | "B" : 22.33,
+ | "C" : -20.0,
+ | "C1" : "20.0}",
+ | "E" : -2233,
+ | "F" : -20.46
+ |}, {
+ | "A" : 4
+ |} ]""".stripMargin
+
+ val actualJson = SparkUtils.convertDataFrameToPrettyJSON(df2)
+
+ compareText(actualJson, expectedJson)
+ }
+ }
+
"write should successfully append" in {
withTempDirectory("cobol_writer3") { tempDir =>
val df = List(("A", "First"), ("B", "Scnd"), ("C", "Last")).toDF("A", "B")
@@ -330,7 +449,15 @@ class FixedLengthEbcdicWriterSuite extends AnyWordSpec with SparkTestBase with B
assert(fs.exists(path), "Output directory should exist")
}
}
-
}
+ def assertArraysEqual(actual: Array[Byte], expected: Array[Byte]): Assertion = {
+ if (!actual.sameElements(expected)) {
+ val actualHex = actual.map(b => f"0x$b%02X").mkString(", ")
+ val expectedHex = expected.map(b => f"0x$b%02X").mkString(", ")
+ fail(s"Actual: $actualHex\nExpected: $expectedHex")
+ } else {
+ succeed
+ }
+ }
}