Skip to content
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -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.
Expand Down
Original file line number Diff line number Diff line change
@@ -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
}
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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
}
Expand Down Expand Up @@ -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)
}
}
}

}
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down Expand Up @@ -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)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
Loading
Loading