Skip to content
Merged
Show file tree
Hide file tree
Changes from all 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
6 changes: 4 additions & 2 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -1684,11 +1684,13 @@ The writer is still in its early stages and has several limitations:
05 FIELD_1 PIC X(1).
05 FIELD_2 PIC X(5).
```
- Only `PIC X(n)` fields are supported; numeric types are not.
- Supported types:
- `PIC X(n)` alphanumeric.
- `PIC S9(n)` numeric (integral and decimal) with `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.
- Only the core EBCDIC encoder is supported; specific EBCDIC code pages are not yet available.
- Save mode `append` is not supported; only `overwrite` is.
- Partitioning by DataFrame fields is not supported.

### Implementation details
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -97,10 +97,11 @@ object BinaryUtils {

def getBytesCount(compression: Option[Usage], precision: Int, isSigned: Boolean, isExplicitDecimalPt: Boolean, isSignSeparate: Boolean): Int = {
import Constants._
val isRealSigned = if (isSignSeparate) false else isSigned

val bytes = compression match {
case Some(comp) if comp == COMP4() || comp == COMP5() || comp == COMP9() => // || comp == binary2()
// if native binary follow IBM guide to digit binary length
case Some(comp) if comp == COMP4() || comp == COMP5() || comp == COMP9() =>
// If native binary follow IBM guide to digit binary length.
// COMP-9 is a little-endian Cobrix extension. It also supports 1 byte binary numbers for 1 and 2 decimal digit PICs.
precision match {
case p if p >= 1 && p <= 2 && comp == COMP9() => 1 // byte
case p if p >= minShortPrecision && p <= maxShortPrecision => binaryShortSizeBytes
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,71 @@
/*
* 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 java.math.RoundingMode

object BinaryEncoders {
def encodeBinaryNumber(number: java.math.BigDecimal,
isSigned: Boolean,
outputSize: Int,
bigEndian: Boolean,
precision: Int,
scale: Int,
scaleFactor: Int): Array[Byte] = {
val bytes = new Array[Byte](outputSize)

if (number == null || precision < 1 || scale < 0 || outputSize < 1)
return bytes

val shift = scaleFactor - scale
val bigInt = if (shift == 0)
number.setScale(0, RoundingMode.HALF_DOWN).toBigIntegerExact
else
number.movePointLeft(shift).setScale(0, RoundingMode.HALF_DOWN).toBigIntegerExact

val intValue = bigInt.toByteArray
val intValueLen = intValue.length

if (intValueLen > outputSize || (!isSigned && bigInt.signum() < 0))
return bytes

val paddingByte = if (bigInt.signum() < 0) 0xFF.toByte else 0x00.toByte

if (bigEndian) {
var i = 0
while (i < outputSize) {
if (i < intValueLen) {
bytes(outputSize - i - 1) = intValue(intValueLen - i - 1)
} else {
bytes(outputSize - i - 1) = paddingByte
}
i += 1
}
} else {
var i = 0
while (i < outputSize) {
if (i < intValueLen) {
bytes(i) = intValue(intValueLen - i - 1)
} else {
bytes(i) = paddingByte
}
i += 1
}
}
bytes
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,8 @@

package za.co.absa.cobrix.cobol.parser.encoding

import za.co.absa.cobrix.cobol.parser.ast.datatype.{AlphaNumeric, COMP3, COMP3U, CobolType, Decimal, Integral}
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 java.nio.charset.{Charset, StandardCharsets}
Expand All @@ -29,16 +30,24 @@ object EncoderSelector {
ebcdicCodePage: CodePage = new CodePageCommon,
asciiCharset: Charset = StandardCharsets.US_ASCII): Option[Encoder] = {
dataType match {
case alphaNumeric: AlphaNumeric if alphaNumeric.compact.isEmpty =>
case alphaNumeric: AlphaNumeric if alphaNumeric.compact.isEmpty =>
getStringEncoder(alphaNumeric.enc.getOrElse(EBCDIC), ebcdicCodePage, asciiCharset, alphaNumeric.length)
case integralComp3: Integral if integralComp3.compact.exists(_.isInstanceOf[COMP3]) =>
case integralComp3: Integral if integralComp3.compact.exists(_.isInstanceOf[COMP3]) =>
Option(getBdcEncoder(integralComp3.precision, 0, 0, integralComp3.signPosition.isDefined, mandatorySignNibble = true))
case integralComp3: Integral if integralComp3.compact.exists(_.isInstanceOf[COMP3U]) =>
case integralComp3: Integral if integralComp3.compact.exists(_.isInstanceOf[COMP3U]) =>
Option(getBdcEncoder(integralComp3.precision, 0, 0, integralComp3.signPosition.isDefined, mandatorySignNibble = false))
case decimalComp3: Decimal if decimalComp3.compact.exists(_.isInstanceOf[COMP3]) =>
case decimalComp3: Decimal if decimalComp3.compact.exists(_.isInstanceOf[COMP3]) =>
Option(getBdcEncoder(decimalComp3.precision, decimalComp3.scale, decimalComp3.scaleFactor, decimalComp3.signPosition.isDefined, mandatorySignNibble = true))
case decimalComp3: Decimal if decimalComp3.compact.exists(_.isInstanceOf[COMP3U]) =>
case decimalComp3: Decimal if decimalComp3.compact.exists(_.isInstanceOf[COMP3U]) =>
Option(getBdcEncoder(decimalComp3.precision, decimalComp3.scale, decimalComp3.scaleFactor, decimalComp3.signPosition.isDefined, mandatorySignNibble = false))
case integralBinary: Integral if integralBinary.compact.exists(_.isInstanceOf[COMP4]) =>
Option(getBinaryEncoder(integralBinary.compact, integralBinary.precision, 0, 0, integralBinary.signPosition.isDefined, isBigEndian = true))
case integralBinary: Integral if integralBinary.compact.exists(_.isInstanceOf[COMP9]) =>
Option(getBinaryEncoder(integralBinary.compact, integralBinary.precision, 0, 0, integralBinary.signPosition.isDefined, isBigEndian = false))
case decimalBinary: Decimal if decimalBinary.compact.exists(_.isInstanceOf[COMP4]) =>
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 _ =>
None
}
Expand Down Expand Up @@ -88,6 +97,27 @@ object EncoderSelector {
buf
}

def getBinaryEncoder(compression: Option[Usage],
precision: Int,
scale: Int,
scaleFactor: Int,
isSigned: Boolean,
isBigEndian: Boolean): Encoder = {
val numBytes = BinaryUtils.getBytesCount(compression, precision, isSigned, isExplicitDecimalPt = false, isSignSeparate = false)
(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)
}
BinaryEncoders.encodeBinaryNumber(number, isSigned, numBytes, isBigEndian, precision, scale, scaleFactor)
}
}

def getBdcEncoder(precision: Int,
scale: Int,
scaleFactor: Int,
Expand Down
Loading
Loading