COBOL CALL "SYSTEM" return value - cobol

I am using Micro Focus COBOL on Windows system and have this code
.
.
01 w-param pic x(100) value 'dir > out.txt'.
.
.
call "SYSTEM" using w-param
Then I have to read out.txt file to get output from dir command. Is there any way to get output from dir (or any other system command) directly to my program as returning value?

Answer - Part 1: NO, you can not have any output of the CALL in the return value.
Answer - Part 2: But you can get the output with a different option.
Explanation for part 1:
"return-values" are normally an integer, passed via the special register RETURN-CODE and/or with the RETURNING clause (in some implementations allowing you to additional get a pointer): CALL someprog RETURNING something, see the COBOL documentation for CALL.
Explanation for part 2:
What you may can do is to create a pipe and read from there, either with calling the C interface or with an implementor-specific extension.
With ACUCOBOL or MicroFocus [and maybe others] you can use pipes via line sequential file access - see the answer of Stephen Gennard for details on MicroFocus and this answer's end for ACUCOBOL.
On unix you can "natively" create a named pipe with CALL 'SYSTEM', a possible way of reading from there is documented in the GnuCOBOL FAQ -> named pipes, in general you can create a pipe and read from it via C interface.
A sample implementation for using pipes via C interface and a COBOL wrapper for it is cobweb-pipes (MF likely supports user defined functions, therefore the cobweb-pipes.cob likely works more or less unchanged (if you test this please answer with a comment), otherwise the cobweb-call-pipes.cob is very likely to work.
Edit:
Extension in ACUCOBOL via SEQUENTIAL files and starting with a -P in the assigned filename:
program-id. dircmdread.
select i-cmd
* windows:
assign to "-P %TMP% cmd.exe /c dir > %TMP%"
* unix:
* assign to "-P ls -l"
organization is sequential.
fd i-cmd.
01 i-cmd-record pic x(80).
procedure division.
open input i-cmd
perform until exit
read i-cmd
at end
exit perform
end-read
display i-cmd-record
end-perform
close i-cmd
goback.

Answer: YES (if you are using Micro Focus COBOL)
You can do it by using pipes via COBOL syntax
For example:
program-id. dircmdread.
select i-cmd
assign to "< cmd.exe /c dir"
organization is line sequential.
fd i-cmd.
01 i-cmd-record pic x(80).
procedure division.
open input i-cmd
perform until exit
read i-cmd
at end
exit perform
end-read
display i-cmd-record
end-perform
close i-cmd
goback.
end program dircmdread.
and execute it via:
Y:\DemoAndTests\dirread>cobol dircmdread.cbl nologo int();
* Generating dircmdread
* Data: 1048 Code: 736 Literals: 424
Y:\DemoAndTests\dirread>run dircmdread
Volume in drive Y is UserSourceCode
Volume Serial Number is EE5F-1112
Directory of Y:\DemoAndTests\dirread
29/09/2016 15:13 <DIR> .
29/09/2016 15:13 <DIR> ..
29/09/2016 15:16 509 dircmdread.cbl
29/09/2016 15:17 2,560 dircmdread.int
29/09/2016 15:17 2,330 dircmdread.obj
3 File(s) 5,399 bytes
2 Dir(s) 20,383,764,480 bytes free

Related

Getting Overlapping error in COBOL program

Cobol program :
PROGRAM-ID. SCHPROG.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT MYFILE ASSIGN TO INDD
ORGANIZATION IS SEQUENTIAL
ACCESS MODE IS SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD MYFILE.
01 FILERECORDS.
05 NAME PIC A(10).
05 CLASS-IN PIC 9(1).
05 ROLL PIC 9(5).
WORKING-STORAGE SECTION.
COPY SCHMAPA.
COPY SCHMAPB.
COPY SCHMAPC.
01 END-OF-FILE PIC A(3) VALUE 'NO'.
PROCEDURE DIVISION.
000-MAIN-PARA.
PERFORM 100-SEND-MAPA.
PERFORM 100-RECEIVE-MAPA.
IF CHOICEI = '1'
PERFORM 200-SEND-MAPB
PERFORM 200-RECEIVE-MAPB
PERFORM 200-SEND-MAPB
PERFORM 100-SEND-MAPA
END-IF.
IF CHOICEI = '2'
PERFORM 300-SEND-MAPC
PERFORM 300-RECEIVE-MAPC
PERFORM 500-SRCH-REC
PERFORM 300-SEND-MAPC
PERFORM 100-SEND-MAPA
END-IF.
STOP RUN.
100-SEND-MAPA.
EXEC CICS
SEND
MAP('SCHOLA') MAPSET('SCHMAPA')
ERASE
END-EXEC.
100-RECEIVE-MAPA.
EXEC CICS
RECEIVE
MAP('SCHOLA') MAPSET('SCHMAPA')
END-EXEC.
200-SEND-MAPB.
EXEC CICS
SEND
MAP('SCHOLB') MAPSET('SCHMAPB')
ERASE
END-EXEC.
200-RECEIVE-MAPB.
EXEC CICS
RECEIVE
MAP('SCHOLB') MAPSET('SCHMAPB')
END-EXEC.
PERFORM 400-FILE-PROCESS.
300-SEND-MAPC.
EXEC CICS
SEND
MAP('SCHOLC') MAPSET('SCHMAPC')
ERASE
END-EXEC.
300-RECEIVE-MAPC.
EXEC CICS
RECEIVE
MAP('SCHOLC') MAPSET('SCHMAPC')
END-EXEC.
400-FILE-PROCESS.
OPEN OUTPUT MYFILE.
MOVE NAMEI TO NAME.
MOVE CLASSI TO CLASS-IN.
MOVE ROLLI TO ROLL.
WRITE FILERECORDS.
CLOSE MYFILE.
MOVE 'RECORD INSERTED' TO MSGBO.
500-SRCH-REC.
OPEN INPUT MYFILE.
PERFORM UNTIL END-OF-FILE = 'YES'
READ MYFILE INTO FILERECORDS
AT END
MOVE 'YES' TO END-OF-FILE
NOT AT END
IF ROLL = ROLLCI
MOVE NAME TO NAMECO
MOVE CLASS-IN TO CLASSCO
END-IF
END-READ
END-PERFORM.
CLOSE MYFILE.
Getting error.
IGYPA3043-E Data-item "FILERECORDS (GROUP)" and record "FILERECORDS (GROUP)"
had overlapping storage. Movement of data may not occur at execution time.
I have provided my cobol program. please check and help me to find the issue.
I am updating file from Cics region and using the same file to get the details and put in cics region.
Not sure why I am getting this error.
Earlier I am using same Group data Item to add record to file and it is working fine.
Please help !!
While the other answers correctly answer your question, compiling for CICS entails some restrictions documented here and quoted as of 06-Apr-2021 below. You may also want to consult the CICS documentation for your version and release of CICS.
Restriction: You cannot run COBOL programs that have object-oriented
syntax for Java™ interoperability in CICS. In addition, if you write
programs to run under CICS, do not use the following code:
FILE-CONTROL entry in the ENVIRONMENT DIVISION, unless the
FILE-CONTROL entry is used for a SORT statement
FILE SECTION of the
DATA DIVISION, unless the FILE SECTION is used for a SORT statement
User-specified parameters to the main program USE declaratives (except
USE FOR DEBUGGING)
These COBOL language statements:
ACCEPT format 1:
data transfer (you can use format-2 ACCEPT to retrieve the system date
and time)
CLOSE
DELETE
DISPLAY UPON CONSOLE
DISPLAY UPON SYSPUNCH
MERGE
OPEN
READ
RERUN
REWRITE
START
STOP literal
WRITE
[...]
Coding file input and output: You must use CICS commands for most input and output processing. Therefore, do not describe files or code
any OPEN, CLOSE, READ, START, REWRITE, WRITE, or DELETE statements.
Instead, use CICS commands to retrieve, update, insert, and delete
data.
READ MYFILE INTO FILERECORDS is a duplicate because those are already assigned to each other.
To fix that simply use READ MYFILE (the INTO somewhere would only be used if you don't want to place that into FILERECORDS but somewhere else).
Similar answer to #simon's.
READ already places the record into the 01 definition in MYFILE. READ INTO is used when you want the data to be placed in another area in WORKING-STORAGE. Executing a READ INTO to the FD area is simply moving the data over itself.
I was always taught to do a READ INTO an area that I defined or was a COPYBOOK in WORKING-STORAGE to separate the I/O area from the data manipulation.
In assembler what you are doing with READ is the equivalent of a GET LOCATE as opposed to a GET MOVE type of operation.

What is the logic to write a COBOL program to reverse records and move from 1 file to another?

For example:
File1
AAA
BBB
CCC
DDD
File2
DDD
CCC
BBB
AAA
What is the logic to write a COBOL program to reverse records and move from 1 file to another?
Addressing a COBOL-only solution, the method for reversing the sequence of records in a file changed between COBOL 85 and COBOL 2002. Specifically, the REVERSED phrase was made obsolete in COBOL 85 and removed in COBOL 2002.
COBOL 85
The following requires the input be fixed-length records with ORGANIZATION SEQUENTIAL.
Code:
environment division.
input-output section.
file-control.
select file1 assign "file1.dat"
organization sequential
.
select file2 assign "file2.dat"
organization sequential
.
data division.
file section.
fd file1.
01 file1-rec pic x(4).
fd file2.
01 file2-rec pic x(4).
working-storage section.
01 eof-flag pic 9 value 0.
88 eof-file1 value 1.
procedure division.
begin.
open input file1 reversed
output file2
perform read-file1
perform until eof-file1
write file2-rec from file1-rec
perform read-file1
end-perform
close file1 file2
stop run
.
read-file1.
read file1
at end
set eof-file1 to true
end-read
.
Input:
AAAABBBBCCCCDDDD
Output:
DDDDCCCCBBBBAAAA
[Note that because these are fixed-length, four-character records, there are no separators and, therefore, the records are not shown on separate lines.]
For RELATIVE or INDEXED files, it is necessary to, first, copy the records to a fixed-length sequential file, then use the above logic to create the "reversed" sequential file. For variable-length records, it is also necessary to save the record length as part of the fixed-length record before using the above reversing. Then, rather than writing fixed-length records, write variable-length records.
COBOL 2002 (untested)
Code:
environment division.
input-output section.
file-control.
select file1 assign "file1.dat"
organization sequential
.
select file2 assign "file2.dat"
organization sequential
.
data division.
file section.
fd file1.
01 file1-rec pic x(4).
fd file2.
01 file2-rec pic x(4).
working-storage section.
01 eof-flag pic 9 value 0.
88 eof-file1 value 1.
procedure division.
begin.
open input file1
output file2
start file1 last
invalid key
set eof-file1 to true
not invalid key
perform read-file1
end-start
perform until eof-file1
write file2-rec from file1-rec
perform read-file1
end-perform
close file1 file2
stop run
.
read-file1.
read file1 previous
at end
set eof-file1 to true
end-read
.
The input file may be SEQUENTIAL, RELATIVE, or INDEXED. If INDEXED, the primary key will be used. ACCESS must be either SEQUENTIAL or DYNAMIC. The records may be either fixed- or variable-length.
COBOL 2002 standard
START statement 14.8.37.3 General rules
SEQUENTIAL FILES
21) If LAST is specified, the file position indicator is set to the record number of the last existing logical record in the physical file. If no records exist in the file, or the physical file does not support the ability to position at the last record, the I-O status value in the file connector referenced by file-name-1 is set to '23', the invalid key condition exists, and the execution of the START statement is unsuccessful.
The above code, will treat the invalid key condition the same as end of file.
You should read the File1, storing the information into a Local Table. When you have all the records read, then you start writing the Local Table in the File 2, in the reverse order.

How to remove end-of-proof symbol?

Every time I'm writing to an output file, there will always be an end-of-proof symbol (□).
Consider the program below:
IDENTIFICATION DIVISION.
PROGRAM-ID. HEY.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT OUTFILE ASSIGN TO "alpha.txt".
DATA DIVISION.
FILE SECTION.
FD OUTFILE.
01 OUTREC PIC X(10).
PROCEDURE DIVISION.
OPEN OUTPUT OUTFILE
MOVE "ABCDEFGHIJ" TO OUTREC
WRITE OUTREC
CLOSE OUTFILE
STOP RUN.
The contents of alpha.txt is
ABCDEFJHIJ
□
I'm using Realia because that is what our school requires us to use. I'm also aware that if I run the same code above using some other compiler such as OpenCobol, the output is just fine, i.e., without the the end-of-proof symbol.
So, how do I remove the end-of-proof symbol?
There is likely no end-of-proof symbol in the file, instead the symbol you see is used for the non-printable character which is in there (or a character without a symbol in the used font; or, as Rick pointed out the end-of-file marker).
From the "txt" extension it looks like you want a text file but as you did not specify anything you end up with a sequential file.
I'm not 100% sure about the support for the (up to COBOL 202x non-standard) ORGANIZATION IS LINE SEQUENTIAL in Realia COBOL, but I suggest to give it a try:
SELECT OUTFILE ASSIGN TO "alpha.txt"
ORGANIZATION IS LINE SEQUENTIAL.
It is almost certainly an end-of-file mark (Cntl-Z or 0x1A). On my system (Win 10) the symbol is displayed as elongated (tall) rather than square. Pasted to this post it is square.
ABCDEFJHIJ
[The square shows in preview and edit; but later disappears.]
See also this answer and this Wikipedia article, End-of-file, for more information.
How to remove end-of-proof symbol?
Reading files in Realia COBOL is not a problem. It may not be a problem with GNUCobol. However, a character by character copy of the file, stopping at the eof-of-file mark, can be done in COBOL or any other language.

Reading cobol file line by line seperated by new line character

I'm having trouble reading a file line-by-line. This is a current snippet of the code:
file-control.
select input-file
assign input-file-name
organization is sequential
file section.
fd input-file.
01 input-file-record picturex(25)
working-storage section.
01 ws-eof picture a(1).
and here's where I actually read in the file:
perform until ws-eof = 'Y'
read input-file into input-file-record
at end move 'Y' to ws-eof
not at end
display input-file-record
end-read
end-perform
close input-file
The problem is, i'm trying to read the file line by line, but it seems like it's just filling up 25 characters, then reading again instead of looping by the return character in the text file.
The text file would look something like this:
AAAA
BBBB
CCCC
DDDD
The problem is, i'm trying to read the file line by line, but it seems like it's just filling up 25 characters, then reading again instead of looping by the return character in the text file.
The system is exactly doing what you tell it to do:
organization is sequential *> sequential, fixed length
01 input-file-record picture x(25) *> the fixed length is 25 bytes
Depending on the compiler you use (it is always a good idea to specify this if there isn't a specific tag for it already that you can use, and even in this case the version number never harms) you can either use the common extension (which may even get standard with COBOL 202x):
organization is line sequential *> sequential, read until line break found
or have to read it sequential (in this case likely with a bigger size) and
inspect file-rec converting all x'0d' by x'0a' *> if you expect windows or mac line breaks
move 1 to strpoint
unstring file-rec
delimited by all x'0a'
into real-rec
with pointer strpoint
end-unstring

Is there a way to parameterize functions in COBOL?

I'm coding routines like:
READ-A.
READ FILE-A
AT END
MOVE 1 TO EOF-A
NOT AT END
ADD 1 TO CN-READ-A
END-READ.
F-READ-A. EXIT.
to read several files and I was wondering if there's a way to code a routine that is able to read the filename from a variable so I don't have to code the same thing for each file. Thanks!
One solution as said above is to use multiple programs or nested program, for which
I have included an example below, which is solution 1.
Another solution is to COBOL classes, which might not be to your liking but I like them, so I've included an example, which is solution 2.
Solution 1:
program-id. TestProgram.
working-storage section.
01 file-name pic x(128).
01 file-lines pic 9(9).
procedure division.
move 0 to file-lines
move "d:\rts_win32.txt" to file-name
call "program1" using file-name file-lines
display file-lines
stop run
end program TestProgram.
program-id. Program1.
file-control.
select file-a assign to myfile
organization is line sequential.
data division.
fd file-a.
01 file-a-line pic x(80).
working-storage section.
01 EOF-A pic 9 value 0.
linkage section.
01 lk-filename pic x(128).
01 CN-READ-A pic 9(9).
procedure division using lk-filename
CN-READ-A.
move lk-filename to myfile
open input file-a
perform READ-A until EOF-A equals 1
close file-a
goback.
READ-A.
READ FILE-A
AT END
MOVE 1 TO EOF-A
NOT AT END
ADD 1 TO CN-READ-A
END-READ.
F-READ-A.
EXIT.
end program Program1.
Solution 2
program-id. TestProgram.:
working-storage section.
01 file-counter type FileLineCounter.
procedure division.
set file-counter to new type FileLineCounter("d:\rts_win32.txt")
display file-counter::LineCount
stop run
end program TestProgram.
class-id FileLineCounter.
file-control.
select file-a assign to myfile
organization is line sequential.
data division.
fd file-a.
01 file-a-line pic x(80).
working-storage section.
01 cn-read-a binary-long property as "LineCount".
method-id New.
01 EOF-A pic 9 value 0.
procedure division using by value filename as string.
set myfile to filename
open input file-a
perform READ-A until EOF-A equals 1
close file-a
goback.
READ-A.
READ FILE-A
AT END
MOVE 1 TO EOF-A
NOT AT END
ADD 1 TO CN-READ-A
END-READ.
F-READ-A.
EXIT.
end method.
end class.
May not be "in the wild" yet with compiler support, but the current ISO Draft 20xx standard includes FUNCTION-ID in place of PROGRAM-ID. It adds a parameter friendly function call computing paradigm to COBOL.
Might not help today, but maybe in the near future. If I'm not mistaken, User Defined Functions are actually from the COBOL 2002 spec, but it seems compiler vendors are hit or miss on support for the feature.
FUNCTION-ID support is in closed trials for OpenCOBOL 2.0, but the timeline for the 2.0 release is undetermined and could be another year or more before it's made public.
The proper Cobol way to parameterize routines is via the nested subprogram.
You can do what you want, but it is dependant upon your compiler and environment, you can pass a file, or a file name, or a DDname.
What platform are you on?
Edit: On z/OS, you can change what FILE-A points to at runtime using putenv() to adjust the dataset name associated with the DDNAME that FILE-A uses.
See:
http://ibmmainframes.com/post-57281.html
http://cicswiki.org/cicswiki1/index.php?title=How_do_I_allocate_a_file_dynamically_using_COBOL%3F
You will need a OPEN-A and CLOSE-A paragraph as well between switching files.
It isn't exactly passing parameters to your read statement, but it lets you reuse your OPEN/READ/WRITE/CLOSE statements for different files. But only serially.
There was a way, under VS COBOL II, where you could pass an FD to a subprogram, that would look something like:
CALL MYREADPGM USING FILE-A
CALL MYREADPGM USING FILE-B
This possible with Enterprise Cobol but IIRC VisualAge does not support that.
I realize this is an old thread, but hopefully someone might find this useful in the future: IBM's Enterprise COBOL on z/OS 6.4 compiler supports user-defined functions (released May 2022). User-defined functions could be a useful alternative to the other suggestion for internal programs. In contrast to program calls, there are compile time checks for parameters to user-defined function invocations. Also, you can invoke the function in a lot of places where you couldn't call a program, like within a
n expression.
Here's an example based on passing a file name to a function. It might be possible to combine this with the PUTENV() suggestion above.
IDENTIFICATION DIVISION.
FUNCTION-ID. READ-FILE.
DATA DIVISION.
LINKAGE SECTION.
1 FILE-NAME PIC X(50).
1 RET PIC 9(9).
PROCEDURE DIVISION USING FILE-NAME RETURNING RET.
* DO STUFF WITH FILE-NAME
* ...
GOBACK
.
END FUNCTION READ-FILE.
IDENTIFICATION DIVISION.
PROGRAM-ID. MAINPROG.
DATA DIVISION.
WORKING-STORAGE SECTION.
1 READ-RESULT PIC 9(9).
PROCEDURE DIVISION.
COMPUTE READ-RESULT = FUNCTION READ-FILE('MYINPUTFILE')
GOBACK
.
END PROGRAM MAINPROG.
More examples can be found in the Programming Guide Chapter 32 Using user-defined functions.
https://www.ibm.com/support/pages/enterprise-cobol-zos-documentation-library#Table642
You could create a data file of filenames, treat each one as an individual record, and then read each file. In the "SELECT ...ASSIGN" you would need to use a working-storage variable for the filename and move the value from the 'file of filenames' into it.
As you are using VisualAge, I assume in UNIX, you might also be able to run the program from the shell (sh,ksh), with the filename as a parameter, and repeatedly run the program from the shell for each file name.

Resources