PC COBOL program to JCL - cobol

I have the following simple COBOL program - written for the PC. It simply reads a file from the computer and writes to the file:
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT CUSTOMER-FILE ASSIGN TO
"C:Customers.dat"
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD CUSTOMER-FILE.
01 CUSTOMER-RECORD.
05 FIRST-NAME PIC X(20).
05 LAST-NAME PIC X(20).
WORKING-STORAGE SECTION.
01 WS-CUSTOMER-RECORD.
05 WS-FIRST-NAME PIC X(20).
05 WS-LAST-NAME PIC X(20).
01 WS-EOF PIC X.
PROCEDURE DIVISION.
OPEN OUTPUT CUSTOMER-FILE
PERFORM UNTIL CUSTOMER-RECORD = SPACES
DISPLAY "Enter the first and last name for the customer"
ACCEPT CUSTOMER-RECORD
WRITE CUSTOMER-RECORD
END-PERFORM
CLOSE CUSTOMER-FILE
DISPLAY "Output from the Customer File:"
OPEN INPUT CUSTOMER-FILE.
PERFORM UNTIL WS-EOF = 'Y'
READ CUSTOMER-FILE INTO WS-CUSTOMER-RECORD
AT END MOVE 'Y' TO WS-EOF
NOT AT END DISPLAY WS-CUSTOMER-RECORD
END-READ
END-PERFORM.
CLOSE CUSTOMER-FILE.
GOBACK.
My question: I'm not too familiar with JCL. So if I were to put this program on a mainframe, what would I do for the JCL?

I presume your Identification Division got lost in a cut & paste incident on its way to Stack Overflow; you'll need that.
The current incarnation of IBM Enterprise COBOL does not allow free format source so in order to get your code to compile you would have to reformat and follow the traditional fixed format.
Rather than referring to your data file by name, your Assign clause must refer to a name (limited to 8 characters) which corresponds to a DD name in your JCL. Pick something meaningful, to the extent you can in 8 characters, maybe CUSTOMER.
Since you're running with JCL, your Accept statement will work a bit differently. Probably data will come from a SYSIN DD.
Your JCL will look something like this...
[job card, which is shop-specific]
//TOMSPGM EXEC PGM=yourProgramName
//STEPLIB DD DISP=SHR,DSN=mainframe.dataset.where.you.bound.your.program
//SYSIN DD *
[your customer records]
//CUSTOMER DD DISP=(NEW,CATLG,DELETE),
// DSN=mainframe.dataset.where.your.data.should.end.up,
// LRECL=40,
// AVGREC=U,
// RECFM=FB,
// SPACE=(40,(10,10),RLSE) Adjust to your needs
//SYSOUT SYSOUT=*
//CEEDUMP SYSOUT=*
I'm not sure how this will work with your creating the customer file and then reading it in the same program. In 30 years of mainframe work I've never seen that.

Adding to answer from #cschneid.
Great to see AVGREC is being used on the DD statement to allocate space for the data set. This is much better than using the old-fashioned CYL, or TRK units.
Unfortunately, IMHO, the IBM z/OS architects missed to implement a more modern was to specify space: KiB, or MiB. (ISPF supports KB, and MB as space unit, JCL doesn't.)
With AVGREC you tell the system that the SPACE= primary and secondary space values are number of records, instead of physical units such as tracks, or cylinders.
//CUSTOMER DD ...
// AVGREC=U,
// SPACE=(40,(10,20),RLSE)
Above statement tells the system that the records written will have an average length of 40 bytes (this completely is independent of RECFM=, or LRECL=!). With AVGREC=U (U means units), this further tells the system to allocate initial (primary) space for 10 records, and to add additional space for 20 records each time more space is needed (with an upper limit).
Physical allocations are still in tracks, or cylinders under the hood. The system calculates tracks, or cylinders needed from
"average record length" * "number of records" * avgrec-unit
For the primary allocation, this is
40 * 10 * 1 = 400 bytes
Good. But how can we specify our space needs in KiB or MiB using these keywords?
Remember that the average record length in the SPACE= parameter is completely unreleated to the actual record length specified via LRECL=. Great, so we can freely choose the average record length, and set it to, say, 1. And let us also change the wording "number of records* in above forumla to "number of units". The formula becomes:
1 * "number of units" * avgrec-unit
or
"number of units" * avgrec-unit
AVGREC= supports the units U (1), K (1024), and M (1024*1024). So, to allocate space in megabytes (MiB), we simply code:
//CUSTOMER DD ...
// AVGREC=M,
// SPACE=(1,(10,20),RLSE)
This will allocate 10 MiB primary space, and 20 MiB secondary space. Each allocation is rounded up to the next integral number of tracks, or cylinders, depending on physical disk structures. You simply don't have to care anymore. Neat, isn't it?

Related

Dynamic memory allocation in COBOL

I have a common C function that I want to call from C, Fortran and COBOL. It fetches x bytes of data from a database and places it in a char pointer supplied to it. My example below fetches 1024 bytes, but in the real situation I want to be able to fetch much larger chunks of data than 1024 bytes as well, hence the dynamic memory allocation.
void fetch_data(char *fetched)
{
static struct {unsigned long data_length; char some_data[1024];} a_struct;
// Fetch data into a_struct.
memcpy(fetched, &(a_struct.some_data), 1024);
}
I was able to call this function successfully from C.
char *mydata;
mydata = malloc(1024);
fetch_data(mydata);
// Do something with the data.
free(mydata);
I was also able to call this function successfully from Fortran.
INTEGER*4, ALLOCATABLE :: MYDATA(:)
ALLOCATE(MYDATA(1024))
CALL FETCH_DATA(MYDATA)
// Do something with the data.
DEALLOCATE(MYDATA)
But how do I allocate and deallocate dynamic memory in COBOL? I have been unable to find built-in functions/procedures for this purpose.
I also don't see an alternative where C could handle the allocation and deallocation for Fortran and COBOL, as they need to access the data outside C.
As you've only talked about "COBOL" without specifying any actual implementation I assume you mean "standard COBOL".
This could mean COBOL85 - which doesn't have this feature but allows you to just define DATA-FOR-C PIC X(1024) and pass this as reference (COBOL85 actually doesn't specify anything about calling into C space but this should work with most if not all COBOL implementations). Note: This is actually more a detail of Acorns answer.
If you want to use real dynamic memory allocation and you mean standard COBOL - no problem with COBOL 2002 as it introduced the statements ALLOCATE and FREE (Note: this is actually the detail of the comments from roygvib and Rick):
77 pointer-variable USAGE POINTER.
77 address-holder PIC X BASED.
ALLOCATE variable-number CHARACTERS RETURNING pointer-variable
SET ADDRESS OF address-holder TO pointer-variable
CALL "fetch_data" USING address-holder
PERFORM stuff
FREE pointer-variable
If you don't use a COBOL implementation that support these statements you'd have to use the implementor specific routines (normally via CALL) to get/release the memory.
MicroFocus/NetCOBOL (see answer of Rick): CBL_ALLOC_MEM/CBL_FREE_MEM[2]
ACUCOBOL: M$ALLOC/M$FREE
IBM: CEEGTST
any COBOL compiler and runtime that allows to directly call C functions (which may adds additional needs as specifying the appropriate CALL-CONVENTION for those): malloc/free
... see your implementor's manual ...
One example with a very old compiler (Micro Focus COBOL v3.2.50). Much of this is taken directly from the supplemental materials. And since I didn't have an equally old C compiler available, I included a COBOL program as a subtitute.
program-id. dynam.
data division.
working-storage section.
1 ptr pointer.
1 mem-size pic x(4) comp-5 value 1024.
1 flags pic x(4) comp-5 value 1.
1 status-code pic x(2) comp-5.
linkage section.
1 mem pic x(1024).
procedure division.
call "CBL_ALLOC_MEM" using ptr
by value mem-size flags
returning status-code
if status-code not = 0
display "memory allocation failed"
stop run
else
set address of mem to ptr
end-if
call "fetch_data" using mem
display mem
call "CBL_FREE_MEM" using mem
returning status-code
if status-code not = 0
display "memory deallocation failed"
stop run
else
set address of mem to null
end-if
stop run
.
end program dynam.
program-id. "fetch_data".
data division.
working-storage section.
1 some-struct pic x(1024) value all "abcd".
linkage section.
1 mem pic x(1024).
procedure division using mem.
move some-struct to mem
exit program
.
end program "fetch_data".
The display (trimmed) is:
abcdabcdabcdabcd...(for 1024 characters total)
Maybe that will be of some help.
If you do not need the entire data in memory, then consider working chunk-by-chunk: allocate fixed-size storage in COBOL, fetch a chunk into it using the C function, work with it and loop to continue with the next chunk. This way you can avoid allocating dynamic memory altogether.
If you are on Z or using Gnu Cobol you can simply call malloc():
CALL "malloc" USING BY VALUE MEM-SIZE
RETURNING MEM-PTR.
CALL "free" USING BY VALUE MEM-PTR.

Data type in COBOL

I have written the following program, I am confused why when I compile the program I get an error saying that A-COL(1,1) is not a numeric value while displaying A-COL(1,1) gives me 1.
IDENTIFICATION DIVISION.
PROGRAM-ID. TEST1.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 DIFF PIC 9(3).
01 ARRAY.
05 A-ROW OCCURS 99 TIMES.
10 A-COL OCCURS 2 TIMES.
15 TABLE-CONTENT PIC 9(3).
PROCEDURE DIVISION.
MOVE 1 TO A-COL(1,1).
MOVE 2 TO A-COL(2,1).
DISPLAY A-COL(1,1).
COMPUTE DIFF = A-COL(1,1) - A-COL(2,1).
DISPLAY DIFF.
STOP RUN.
Change the A-COL definition to
"10 A-COL PIC 9(3) OCCURS 2 TIMES."
and remove the TABLE-CONTENT.
Group variables are considered alphanumeric (X type) so cannot be used in a computation.
Alternatively you may do this - refer to the address location using the actual numeric field.
PROCEDURE DIVISION.
MOVE 1 TO TABLE-CONTENT(1,1).
MOVE 2 TO TABLE-CONTENT(2,1).
DISPLAY A-COL(1,1).
COMPUTE DIFF = TABLE-CONTENT(1,1) - TABLE-CONTENT(2,1).
DISPLAY DIFF.
Also you might want to make DIFF signed.
Additional Information
A-COL(1,1) displays "1" because it stores the data as "1xx" where x = space. That is not a numeric value. When you run the solutions here you will notice that display line produces "001".
Keep your WORKING-STORAGE structure the same. However, your data-elements are not A-COL, but THE-CONTENT. So use THE-CONTENT, not A-COL.
IDENTIFICATION DIVISION.
PROGRAM-ID. TEST1.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 DIFF PIC S9(3).
01 ARRAY.
05 A-ROW
OCCURS 99 TIMES.
10 A-COL
OCCURS 2 TIMES.
15 TABLE-CONTENT PIC 9(3).
PROCEDURE DIVISION.
MOVE 1 TO TABLE-CONTENT ( 1 1 )
MOVE 2 TO TABLE-CONTENT ( 2 1 )
DISPLAY
">"
TABLE-CONTENT ( 1 1 )
"<"
COMPUTE DIFF = TABLE-CONTENT ( 1 1 )
- TABLE-CONTENT ( 2 1 )
DISPLAY
">"
DIFF
"<"
STOP RUN
.
Your structure is better, because it is easier to maintain. If you ever want to REDEFINES TABLE-CONTENT, you can, without changing the structure. Not so if you "complicate" the structure now.
Yes, if you MOVE a numeric literal to a group-item, an alpha-numeric MOVE is carried out, the result will be your literal left-justified and space-padded to the right, or truncated to the right, or just fitting, depending on the size of your literal.
Although conceptually you have "columns" in your table (COBOL doesn't have arrays, it has tables with OCCURS), be aware that you cannot access a column as a whole. In storage you have row-1-col-1, row-1-col-2, row-2-col-1, row-2-col-2 through to row-99-col-1, row-99-col-2.
Any arithmetic (ADD, SUBTRACT, MULTIPLY, DIVIDE and COMPUTE) can only use numeric fields or literals as source-data. It is not enough that a field contains "a number", it must be a numeric field.
The GIVING (of ADD, SUBTRACT, MULTIPLY and DIVIDE) can place the result in a non-numeric field of a particular type, a numeric-edited field. This is a field with a PICture clause containing numeric-editing PICture symbols.

How to display an absolute value

Given the following code:
IDENTIFICATION DIVISION.
PROGRAM-ID. FABS.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 NUM PIC 9 VALUE ZEROS.
01 ABSVAL PIC 99 VALUE ZEROS.
PROCEDURE DIVISION.
PROGRAM-BEGIN.
DISPLAY "This program returns the absolute value of a number.".
DISPLAY SPACE.
DISPLAY "Input value: " WITH NO ADVANCING.
ACCEPT NUM.
IF (NUM = -0) THEN
COMPUTE ABSVAL = 0
ELSE
IF (NUM > 0) THEN
COMPUTE ABSVAL = 0
ELSE
COMPUTE ABSVAL = ABSVAL * -1
END-IF
END-IF.
DISPLAY "|", NUM "| = ", ABSVAL.
PROGRAM-DONE.
STOP RUN.
Why is the output zero? Is there something wrong? And how do you make a signed/negative input?
Thinking of your task, rather than why you get zero, it is easy.
Let's assume you get a signed value with your ACCEPT.
01 value-from-accept PIC S9.
01 absolute-value-for-output PIC 9.
MOVE value-from-accept TO absolute-value-for-output
DISPLAY
"|"
value-from-accept
"| = "
absolute-value-for-output
You may think that something is wrong with the output from value-from-accept (depending on compiler) but you can always MOVE it to a numeric-edited field and DISPLAY that.
Tip: To reverse the sign of a signed field.
SUBTRACT field-to-reverse-sign
FROM ZERO
GIVING the-reversed-field
SUBTRACT is faster than MULTIPLY.
You have defined your field which is ACCEPTed as unsigned.
The first two "legs" of your nested-IF set ABSVAL to zero. The remaining leg takes the existing value of ABSVAL (from the VALUE ZEROS, so it is zero) and multiplies it by minus one. Getting -ve zero (possibly), but then storing it in an unsigned field. So ABSVAL will always be zero when you come to the DISPLAY.
You define a signed field by prefixing the PICture string with an S:
01 a-signed-field PIC S9(5).
Depending on your compiler, you can type a - when entering the data and it'll be held happily as a negative value in a signed field (which you have to define) or you have to code for it yourself.
after your correction above
I am not sure how you are testing it but to just to ensure that the values are stored correct you may want to have both the fields signed i.e. pic S9 or pic S99. Its possible that without the preceding S (sign) the variables are not really storing the negative sign regardless of what the screen is showing.
pls observe what results you get then

use SHA1 with COBOL

I was wondering if there's any way to apply SHA1 hash with COBOL.
If there's at least some info of how the SHA1 algorithm works it will be usefull.
Thanks
You didn't say which Cobol platform. If you are on z/OS, there are a variety of cryptography services that are easily called from Cobol. And SHA1 is available among those services.
I did a small sample embedding Python in COBOL, and picked an MD5 checksum as an example.
I wouldn't necessarily go with Python, but if you are lucky enough to be able to use OpenCOBOL, then all the features of libcrypto are a simple CALL away.
For completeness, having mentioned the Python angle, but again that's pretty hefy baggage if the goal is simply cryptography. In which case OpenSSL would be a much tighter fit. This listing is very likely NOT suitable for your needs, but it shows off the power of CALL and the C application binary interface. Please excuse me if this is just noise.
From SourceForge:
Very high level Python embedding is pretty straight forward, been there, done that.
>>SOURCE FORMAT IS FIXED
*> *******************************************************
*> Author: Brian Tiffin
*> Date: 20130126
*> Purpose: Embed Python
*> Tectonics: cobc -x cobpy.cob -lpython2.6
*> *******************************************************
identification division.
program-id. cobpy.
procedure division.
call "Py_Initialize"
on exception
display "link cobpy with -lpython2.6" end-display
end-call
call "PyRun_SimpleString" using
by reference
"from time import time,ctime" & x"0a" &
"print('Today is', ctime(time()))" & x"0a" & x"00"
on exception continue
end-call
call "Py_Finalize" end-call
goback.
end program cobpy.
Giving
$ cobc -x cobpy.cob -lpython2.6
$ ./cobpy
('Today is', 'Sat Jan 26 20:01:41 2013')
Python dutifully displayed the tuple.
But what fun is Python if it is just for high level script side effects? Lots, but still.
Pure embedding.
>>SOURCE FORMAT IS FIXED
*> *******************************************************
*> Author: Brian Tiffin
*> Date: 20130126
*> Purpose: Embed Python
*> Tectonics: cobc -x cobkat.cob -lpython2.6
*> NOTES: leaks, no Py_DECREF macros called.
*> *******************************************************
identification division.
program-id. cobkat.
data division.
working-storage section.
77 python-name usage pointer.
77 python-module usage pointer.
77 python-dict usage pointer.
77 python-func usage pointer.
77 python-stringer usage pointer.
77 python-args usage pointer.
77 python-value usage pointer.
01 cobol-buffer-pointer usage pointer.
01 cobol-buffer pic x(80) based.
01 cobol-string pic x(80).
01 cobol-integer usage binary-long.
01 command-line-args pic x(80).
*> *******************************************************
procedure division.
call "Py_Initialize"
on exception
display "link cobpy with -lpython" end-display
end-call
*> Python likes module names in Unicode
call "PyUnicodeUCS4_FromString" using
by reference "pythonfile" & x"00"
returning python-name
on exception
display "unicode problem" end-display
end-call
*> import the module, using PYTHONPATH
call "PyImport_Import" using
by value python-name
returning python-module
on exception
display "this would be borked" end-display
end-call
if python-module equal null
display "no pythonfile.py in PYTHONPATH" end-display
end-if
*> within the module, an attribute is "pythonfunction"
call "PyObject_GetAttrString" using
by value python-module
by reference "pythonfunction" & x"00"
returning python-func
on exception continue
end-call
*>
*> error handling now skimped out on
*>
*> pythonfunction takes a single argument
call "PyTuple_New" using
by value 1
returning python-args
end-call
*> of type long, hard coded to the ultimate answer
call "PyLong_FromLong" using
by value 42
returning python-value
end-call
*> set first (only) element of the argument tuple
call "PyTuple_SetItem" using
by value python-args
by value 0
by value python-value
end-call
*> call the function, arguments marshalled for Python
call "PyObject_CallObject" using
by value python-func
by value python-args
returning python-value
end-call
*> we know we get a long back, hopefully 1764
call "PyLong_AsLong" using
by value python-value
returning cobol-integer
end-call
display "Python returned: " cobol-integer end-display
*> **************************************************** *<
*> a function taking string and returning string
call "PyObject_GetAttrString" using
by value python-module
by reference "pythonstringer" & x"00"
returning python-stringer
end-call
call "PyTuple_New" using
by value 1
returning python-args
end-call
*> Use the OpenCOBOL command argument
accept command-line-args from command-line end-accept
call "PyString_FromString" using
by reference
function concatenate(
function trim(command-line-args)
x"00")
returning python-value
end-call
*> Set the function argument tuple to the cli args
call "PyTuple_SetItem" using
by value python-args
by value 0
by value python-value
end-call
*> call the "pythonstringer" function
call "PyObject_CallObject" using
by value python-stringer
by value python-args
returning python-value
end-call
*> return as String (with the MD5 hex digest tacked on)
call "PyString_AsString" using
by value python-value
returning cobol-buffer-pointer
end-call
*> one way of removing null while pulling data out of C
set address of cobol-buffer to cobol-buffer-pointer
string
cobol-buffer delimited by x"00"
into cobol-string
end-string
display "Python returned: " cobol-string end-display
*> and clear out <*
call "Py_Finalize" end-call
goback.
end program cobkat.
with pythonfile.py
#
# Simple Python sample for OpenCOBOL embedding trial
#
def pythonfunction(i):
return i * i
import hashlib
def pythonstringer(s):
sum = hashlib.md5()
sum.update(s)
return s + ": " + sum.hexdigest()
Giving
$ ./cobkat Python will use this for MD5 hash
no pythonfile.py in PYTHONPATH
Attempt to reference unallocated memory (Signal SIGSEGV)
Abnormal termination - File contents may be incorrect
Oops
$ export PYTHONPATH=.
$ ./cobkat Python will use this for MD5 hash
Python returned: +0000001764
Python returned: Python will use this for MD5 hash: c5577e3ab8dea11adede20a1949b5fb3
Haven't done one of these in a while, fun.
Cheers,
Brian
Oh, in case you're reading along, 1764 is the ultimate answer, squared.
Here's a more on point source listing. Requires OpenCOBOL 1.1CE for the OC_CBL_DUMP
First up, is paying homage to the authors of OpenSSL. They deserve credits.
OpenSSL License
---------------
/* ====================================================================
* Copyright (c) 1998-2011 The OpenSSL Project. All rights reserved.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
*
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
*
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in
* the documentation and/or other materials provided with the
* distribution.
*
* 3. All advertising materials mentioning features or use of this
* software must display the following acknowledgment:
* "This product includes software developed by the OpenSSL Project
* for use in the OpenSSL Toolkit. (http://www.openssl.org/)"
*
* 4. The names "OpenSSL Toolkit" and "OpenSSL Project" must not be used to
* endorse or promote products derived from this software without
* prior written permission. For written permission, please contact
* openssl-core#openssl.org.
*
* 5. Products derived from this software may not be called "OpenSSL"
* nor may "OpenSSL" appear in their names without prior written
* permission of the OpenSSL Project.
*
* 6. Redistributions of any form whatsoever must retain the following
* acknowledgment:
* "This product includes software developed by the OpenSSL Project
* for use in the OpenSSL Toolkit (http://www.openssl.org/)"
*
* THIS SOFTWARE IS PROVIDED BY THE OpenSSL PROJECT ``AS IS'' AND ANY
* EXPRESSED OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
* PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE OpenSSL PROJECT OR
* ITS CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
* SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
* LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
* HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
* STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
* ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED
* OF THE POSSIBILITY OF SUCH DAMAGE.
* ====================================================================
*
* This product includes cryptographic software written by Eric Young
* (eay#cryptsoft.com). This product includes software written by Tim
* Hudson (tjh#cryptsoft.com).
*
*/
Original SSLeay License
-----------------------
/* Copyright (C) 1995-1998 Eric Young (eay#cryptsoft.com)
* All rights reserved.
*
* This package is an SSL implementation written
* by Eric Young (eay#cryptsoft.com).
* The implementation was written so as to conform with Netscapes SSL.
*
* This library is free for commercial and non-commercial use as long as
* the following conditions are aheared to. The following conditions
* apply to all code found in this distribution, be it the RC4, RSA,
* lhash, DES, etc., code; not just the SSL code. The SSL documentation
* included with this distribution is covered by the same copyright terms
* except that the holder is Tim Hudson (tjh#cryptsoft.com).
*
* Copyright remains Eric Young's, and as such any Copyright notices in
* the code are not to be removed.
* If this package is used in a product, Eric Young should be given attribution
* as the author of the parts of the library used.
* This can be in the form of a textual message at program startup or
* in documentation (online or textual) provided with the package.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* "This product includes cryptographic software written by
* Eric Young (eay#cryptsoft.com)"
* The word 'cryptographic' can be left out if the rouines from the library
* being used are not cryptographic related :-).
* 4. If you include any Windows specific code (or a derivative thereof) from
* the apps directory (application code) you must include an acknowledgement:
* "This product includes software written by Tim Hudson (tjh#cryptsoft.com)"
*
* THIS SOFTWARE IS PROVIDED BY ERIC YOUNG ``AS IS'' AND
* ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
* FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
* DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
* OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
* HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
* LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
* OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
* SUCH DAMAGE.
*
* The licence and distribution terms for any publically available version or
* derivative of this code cannot be changed. i.e. this code cannot simply be
* copied and put under another distribution licence
* [including the GNU Public Licence.]
*/
And some COBOL to exercise the cryptography and the two forms of SHA1 hashing
>>source format is free
*> ***************************************************************
*> Author: Brian Tiffin
*> Date: 20130321
*> Purpose: Compute an SHA1 digest, whole
*> Tectonics: cobc -x sha1a.cob -lcrypto
*> ***************************************************************
IDENTIFICATION DIVISION.
program-id. sha1a.
data division.
working-storage section.
01 sha1-digest pic x(20).
01 digestable pic x(80) value "this message needs to be verified".
*> ***************************************************************
procedure division.
*> Compute disgest from block of memory
call "SHA1" using
by reference digestable
by value function length(function trim(digestable))
by reference sha1-digest
on exception
display "link sha1.cob with OpenSSL's libcrypto" end-display
end-call
*> Dump the hash, as it'll unlikely be printable
call "CBL_OC_DUMP" using
by reference sha1-digest
on exception continue
end-call
goback.
end program sha1a.
With a sample run of
$ cobc -x sha1a.cob
$ ./sha1a
link sha1.cob with OpenSSL's libcrypto
Offset HEX-- -- -- -5 -- -- -- -- 10 -- -- -- -- 15 -- CHARS----1----5-
000000 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20 20
000016 20 20 20 20
$ cobc -x sha1a.cob -lcrypto
$ ./sha1a
Offset HEX-- -- -- -5 -- -- -- -- 10 -- -- -- -- 15 -- CHARS----1----5-
000000 c7 3b 52 0c 61 39 9b f9 a5 2f fe 3f 11 90 5e 10 .;R.a9.../.?..^.
000016 3b 0d 15 c5 ;...
And a more complete example, building the digest from multiple updates.
Assumptions here: This will crack on files with trailing spaces.
>>source format is free
*> ***************************************************************
*> Author: Brian Tiffin
*> Date: 20130321
*> Purpose: Compute an SHA1 digest, by piece
*> Tectonics: cobc -x sha1.cob -lcrypto
*> ***************************************************************
IDENTIFICATION DIVISION.
program-id. sha1.
environment division.
configuration section.
input-output section.
file-control.
select samplefile
assign to "sha1.cob"
organization is line sequential
file status is sample-status
.
DATA DIVISION.
file section.
fd samplefile.
01 input-line pic x(2048).
working-storage section.
01 sha1-context usage pointer.
01 sha1-libresult usage binary-long.
88 sha1-success value 1 when set to false is 0.
01 sha1-digest pic x(20).
01 sample-status pic 9999.
01 sample-file-state pic 9.
88 no-more-sample value 9 when set to false is 0.
01 sha-ctx-structure pic x(1024).
*> ***************************************************************
PROCEDURE DIVISION.
*> Compute disgest from a sequential file
open input samplefile
if sample-status not equal to zero
display "Status of " sample-status " returned from open" end-display
display "rest of sample run will be garbage" end-display
end-if
*> Init the SHA1 internals
set sha1-context to address of sha-ctx-structure
call "SHA1_Init" using
by value sha1-context
returning sha1-libresult
on exception
display "Can't find SHA1_Init. hint: cobc -x sha1 -lcrypto" end-display
end-call
if not sha1-success
display "Could not initialize SHA1 structures" end-display
display "normally you'd want to stop run and call the emergency hotline to wake up the support techs, but this is an example and blindly continues." end-display
end-if
*> loop across some data, ignoring issue of trailing spaces on input lines
read samplefile at end set no-more-sample to true end-read
if input-line equal spaces then
move x"0a" to input-line(1:1)
else
move function concatenate(function trim(input-line trailing), x"0a") to input-line
end-if
perform until no-more-sample
call "SHA1_Update" using
by value sha1-context
by content function trim(input-line trailing)
by value function length(function trim(input-line trailing))
on exception display "internal update failure of SHA1_Update" end-display
end-call
if not sha1-success
display "Could not update SHA1 structures" end-display
display "normally you'd want to stop run." end-display
end-if
read samplefile at end set no-more-sample to true end-read
if input-line equal spaces then
move x"0a" to input-line(1:1)
else
move function concatenate(function trim(input-line trailing), x"0a") to input-line
end-if
end-perform
*> finalize the disgest
call "SHA1_Final" using
by reference sha1-digest
by value sha1-context
on exception display "you're kidding right? internal failure of SHA1_Final" end-display
end-call
close samplefile
*> Dump the hash, as it'll unlikely be printable
call "CBL_OC_DUMP" using
by reference sha1-digest
on exception continue
end-call
goback.
END PROGRAM sha1.
and another sample run of
$ cobc -x sha1.cob -lcrypto
$ ./sha1
Offset HEX-- -- -- -5 -- -- -- -- 10 -- -- -- -- 15 -- CHARS----1----5-
000000 d4 04 4b ed 02 e8 ef 54 e0 c4 73 0b 6b 51 85 bc ..K....T..s.kQ..
000016 85 73 d3 16 .s..
$ openssl sha1 sha1.cob
SHA1(sha1.cob)= d4044bed02e8ef54e0c4730b6b5185bc8573d316
SHA1 rquires a lot of bitwise operations (XOR,AND,OR) which are not generally supported in COBOL (they are supported by a few compilers).
Your best bet would be to simply adjust one of the many C implementations so it can be easily called as a COBOL subroutine.
Information on your platform and compiler would be useful.
Yes, there's a way to apply SHA1 hash with COBOL.
I have written the SHA256 hashing algorithm in COBOL, with heaps of telemetry everywhere to let you know exactly what is going on at all points along the way.
If you can do SHA256 in COBOL, you can do SHA-1 in COBOL.
Don't squib it by hashing small input character strings.
Make sure your program works for reams of input characters, so that it can be used for document authentication.
If you've understood the entire specs, then your result for that will be correct as well.
And then, see if you can hash the hash - like bitcoin does.
That is a little bit more tricky than it looks like on face value.
I have assumed that you have to do the coding in COBOL itself,
so that YOU do the real work - not just call a subprogram which someone else has written.
Anyone could do that, so you wouldn't be asking if it was just that.
Look on Github to see how the SHA256 algorithm works.
It also shows example animated intermediate calculations, not just the final result.
IMO finding the full specification is BY FAR the hardest thing.
There's a number of youtube videos, but they are describing only a few tiny parts of the full story.
But if you have ANY weakness in your COBOL skills, especially table processing, but also in structuring your code, EVEN IF YOU FINALLY UNDERSTAND THE SPECS, you'll have a lot of trouble converting SPECS into working code, depending on how you want to get your code written. Transform centred design helps.
This link is a good help as well.
https://hackernoon.com/how-sha-2-works-a-step-by-step-tutorial-sha-256-46103t6k
Use it AND the Github stuff together, but they don't both use the same example input string.
In summary, this about your analysis skills, design skills, coding skills and testing skills - if you want it to be.
Good Luck.
Let us all know how you go.
Added 18th July 2021
FYI
https://github.com/DoHITB/CryptoCobol/blob/main/SHA1HEX.CBL

Cobol storing file to table

I'm trying to store a pattern received from text file into a table in COBOL.
I am using READ.. INTO.. statement to do so, and here is what I have so far.
WORKING-STORAGE SECTION.
01 ROWCOL.
03 NROW PIC 9(3).
03 NCOL PIC 9(2).
01 PATT-INIT.
03 ROW PIC X OCCURS 1 TO 80 TIMES
DEPENDING ON NCOL.
01 PATT.
03 COL OCCURS 1 TO 80 TIMES
DEPENDING ON NCOL.
05 ROW OCCURS 1 TO 100 TIMES
DEPENDING ON NROW PIC X.
PROCEDURE DIVISION.
MAIN-PARAGRAPH.
OPEN INPUT INPUT-FILE.
READ INPUT-FILE INTO ROWCOL.
PERFORM READ-PATTERN
STOP RUN.
READ-PATTERN.
READ INPUT-FILE INTO PATT-INIT(1:NCOL).
The pattern in the input.txt would look something like this:
011000
001010
010100
The thing about this is that, I'm not sure how to place the PATT-INIT array into the PATT 2d-array. I'm only using the PATT-INIT array to receive row-by-row the pattern in each line. Then, I'm trying to store it into PATT 2d array such that I can access each number by the index numbers. e.g. PATT(1:2) would return 1.
Please give me some pointers on how to implement this. If READ.. INTO.. is not the way to go, I'm more than happy to receive other suggestions.
I think part of your problem is that you think things like (1:NCOL) are doing one thing, when in fact they mean something completely different. The notation indicate "reference modification". You probably are expecting ordinary subscripting, or at least "reference modification" from a variable starting point with a fixed length of one.
01 a-nicely-name-table.
05 FILLER OCCURS 80 TIMES.
10 a-nicely-named-row-entry.
15 FILLER OCCURS 6 TIMES.
20 a-nicely-named-column-entry PIC X.
The data from your READ goes into a-nicely-name-row-entry ( subscripted ). Once everything is there, you can reference a paricular column on a particula row by a-nicely-named-column-entry ( a-row-subcript, a-column-subscript ).
Note, without the ":" this is subscripting, not "reference modification". The comma is optional.
You need to ensure that you don't go "outside" the bounds of the number of rows you put in the table, and also that you do not "overflow" the table with input data.
You can use indexes for subscripting (INDEXED BY on the OCCURS definition). I haven't in the example, as it is unclear what you are trying to achieve.
If I am understanding your question properly, there may be a couple of problems. Bill an Bruce have noted
that you seem to be mixing up subscript and reference modification. Basically
something like:
DISPLAY PATT-INT (1:3)
will display the first 3 characters of PATT-INT. This is a reference modification. While
DISPLAY ROW OF PATT (1, 3)
will display the character at COL 1, ROW 3 of the PATT table. Notice that you need to reference the "lowest" level element name here so maybe renaming some of your data structures make it a little easier to "follow".
The other problem might be a confusion between rows and columns...
The input-txt file you gave has 3 lines of data (rows). Each line has 6 characters (columns). Your
declaration of PATT-INIT seems to re-enforce that since it has an OCCURS NCOL times. When you read one
line of data you get 6 columns for that row. However, the PATT
table flips this on its side. It is declared with a Column then Row layout.
This layout means you cannot read directly into it from input.txt because the table declaration
does not follow the file layout.
Two solutions to that problem.
This is the one I think you might have been trying to work toward:
Read each input.txt line and store it in PATT such that it
becomes 6 columns in PATT for the same row. For example the first row of input: 011000 would be
stored in PATT (1, 1) through PATT (6, 1), 6 columns, 1 row. Note: You
indicated that ROW OF PATT (1, 2) should have a value of '1' - here ROW OF PATT (2, 1) would be '1'.
That aside, you could read one line of input into a single dimension array (PATT-INIT) and then
redistribute it into
the PATT table. Here is a program outline:
MAIN-PARAGRAPH.
OPEN INPUT INPUT-FILE
READ INPUT-FILE INTO ROWCOL
PERFORM VARYING WS-R FROM 1 BY 1
UNTIL WS-R > NROW
PERFORM READ-1-ROW
END-PERFORM
CLOSE INPUT-FILE
.
READ-1-ROW.
READ INPUT-FILE INTO PATT-INIT (1:NCOL)
PERFORM VARYING WS-C FROM 1 BY 1
UNTIL WS-C > NCOL
MOVE ROW OF PATT-INIT (WS-C) TO ROW OF PATT (WS-C, WS-R)
END-PERFORM
.
The other solution might to be redefine PATT as
01 PATT.
03 ROW OCCURS 1 TO 100 TIMES
DEPENDING ON NROW.
05 COL OCCURS 1 TO 80 TIMES
DEPENDING ON NCOL PIC X.
Now you can simply read as follows:
MAIN-PARAGRAPH.
OPEN INPUT INPUT-FILE
READ INPUT-FILE INTO ROWCOL
PERFORM VARYING WS-R FROM 1 BY 1
UNTIL WS-R > NROW
READ INPUT-FILE INTO ROW (WS-R) (1:NCOL)
END-PERFORM
CLOSE INPUT-FILE
You can drop the PATT-INIT working storage since it is no longer referenced.
Note: With this layout COL OF PATT (1, 2) = '1'
Flesh out the above with proper data edits, bounds checks and FILE-STATUS checking after each I/O to
complete the program.
The problem is not the read into it is with PATT-INIT(1:NCOL). This is called
Reference Modification.
Cobol does Line or record orientated IO. so
READ INPUT-FILE INTO PATT-INIT
is probably what you want. To access an array element use (i,j) not (i:j)

Resources