Reputation: 58324
I have the following COBOL subroutine that accepts a string, a length, and a "boolean" argument. The subroutine displays the string without the trailing blanks. The length is provided in the event that the input string's full length is different than the storage used in the subroutine for the string argument. The "boolean" indicates whether there should be a line advance after displaying the string.
IDENTIFICATION DIVISION.
PROGRAM-ID. Display-String.
DATA DIVISION.
LOCAL-STORAGE SECTION.
01 i PIC 9(3).
01 Len PIC 9(3).
LINKAGE SECTION.
01 LS-Input-String PIC X(255).
01 LS-Input-Length PIC 9(3).
01 LS-Advancing PIC X.
88 LS-Advance VALUE 'T' WHEN SET TO FALSE 'F'.
PROCEDURE DIVISION USING LS-Input-String, LS-Input-Length,
LS-Advancing.
MOVE LENGTH OF LS-Input-String TO Len
IF ADDRESS OF LS-Input-Length NOT = NULL THEN
MOVE FUNCTION MIN(LS-Input-Length Len) TO Len
END-IF
PERFORM VARYING i FROM Len BY -1
UNTIL i LESS THAN 1 OR LS-Input-String(i:1) NOT = ' '
END-PERFORM
IF i > ZERO
IF LS-Advance THEN
DISPLAY LS-Input-String(1:i)
ELSE
DISPLAY LS-Input-String(1:i) WITH NO ADVANCING
END-IF
ELSE
IF LS-Advance THEN
DISPLAY ' '
END-IF
END-IF
GOBACK.
This works fine when I call it as:
MOVE LENGTH OF WS-My-String TO WS-Length
CALL 'Display-String' USING WS-My-String, WS-Length, 'F'
But I get erroneous results for this (the subroutine doesn't get 10
but blanks or something):
CALL 'Display-String' USING WS-My-String, 10, 'F'
So it's not accepting a literal for the second argument, even though it interprets the 3rd argument literal fine.
The random questions I came up with while writing this subroutine are:
Are literals even allowed as arguments in a CALL
? I've read through documentation but having trouble figuring that out. I haven't found examples of literals, but no explicit statements to the contrary. I'm suspecting that passing 'F'
literally is wrong but "happens to work".
Is there a better way of handling strings of various lengths in a function like this?
Is there a more canonical way of issuing a line feed to the output besides DISPLAY ' '
, and without displaying a space?
Ideally, I'd like to be able to omit an argument and let defaults take over in the CALL
, but I got some kind of memory reference error when I attempted to do something like: CALL 'Display-String' USING OMITTED, 0, 'F'
. I read some documentation on OMITTED
but not understanding how to make it work.
I'm using cobc (OpenCOBOL) 1.1.0
on Linux version 3.9.10-100.fc17.i686.PAE (Fedora 17).
Upvotes: 2
Views: 1713
Reputation: 13076
A CALL
statement has three options for the USING: BY REFERENCE
; BY CONTENT
; BY VALUE
; OMITTED
. OK, four then counting that last one.
They default when specified is BY REFERENCE. The latest option specified refers to the following items on the CALL ... USING ... until another option appears.
Applying those to what you have coded, all your USING items are BY REFERENCE.
Yes, literals are allowed in CALL statements. Literals can only be used BY CONTENT or BY VALUE. So your CALL should be:
CALL 'Display-String' USING BY REFERENCE
WS-My-String
BY CONTENT
10
BY CONTENT
'F'
Or:
CALL 'Display-String' USING BY REFERENCE
WS-My-String
BY VALUE
10
BY VALUE
'F'
If you use BY VALUE you'd also have to specify BY VALUE on the matching PROCEDURE DIVISION USING ... (or ENTRY ... USING ...) item.
However, that is not the end of your story for the literal, because there is a bug. I'd suggest you consider upgrading to GnuCOBOL (the new name for OpenCOBOL) 2.0. You can find discussion of this issue in the GnuCOBOL discussion area at SourceForge.Net. It will be fixed. If you're keen, you can fix it yourself and get that included in the source...
Should cover questions one and two.
Third, interesting question. Not a canonical-for-COBOL way, as COBOL itself does not have line-feeds and such-like. A good question for the GnuCOBOL area. You can DISPLAY a hexadecimal literal of the appropriate value, but that won't be transportable. Various COBOL compilers have language extensions on DISPLAY. Whether any can be used when there is no data to DISPLAY, I don't know. There is a Z-literal, which is a literal "terminated" by a binary-zero, but I don't think the literal-content can be "missing". Others will have opinions and ideas.
Fourth, you should be able to use OMITTED on your CALL. You can't use OMITTED for a BY VALUE item, but it can be used for BY REFERENCE and BY CONTENT items.
Being able to use it also means being able to deal with it in your CALLed program. If you CALL your program with the string OMITTED your program will fail, as it is assuming that there is a field/value there to access, and there won't be.
OK, some review.
PROCEDURE DIVISION USING LS-Input-String, LS-Input-Length,
LS-Advancing.
Commas in code do nothing. If you want to highlight separateness:
PROCEDURE DIVISION USING LS-Input-String
LS-Input-Length
LS-Advancing
.
If someone leaves ,,
lying around by accident, someone else may think "it must mean something".
MOVE LENGTH OF LS-Input-String TO Len
IF ADDRESS OF LS-Input-Length NOT = NULL THEN
MOVE FUNCTION MIN(LS-Input-Length Len) TO Len
END-IF
There are two ways to get at the length of an identifier: LENGTH OF
; FUNCTION LENGTH
. The latter allows this instead:
IF ADDRESS OF LS-Input-Length NOT = NULL
MOVE FUNCTION MIN (
LS-Input-Length
FUNCTION LENGTH (
LS-Input-String
)
)
TO Len
END-IF
However:
MOVE LENGTH OF LS-Input-String TO Len
IF ADDRESS OF LS-Input-Length NOT = NULL THEN
IF LS-Input-Length LESS THAN Len
MOVE LS-Input-Length TO Len
END-IF
END-IF
Is, to me, clearer and will perform better if you happen to be doing lots of them.
I don't jam things together. On other compilers you'd get at least some diagnostic message from this:
LS-Input-String(i:1)
I'd make it, and similar:
LS-Input-String ( i : 1 )
At a minimum there should be blanks around the brackets themselves.
To check for entirely blank I... check for entirely blank, but earlier. Save the loop in that case, simplifies the terminal condition for the loop:
IF LS-Input-String EQUAL TO SPACE
IF LS-Advance
DISPLAY ' '
END-IF
ELSE
PERFORM VARYING i FROM Len BY -1
UNTIL LS-Input-String ( i : 1 )
NOT EQUAL TO SPACE
END-PERFORM
IF LS-Advance THEN
DISPLAY LS-Input-String ( 1 : i )
ELSE
DISPLAY LS-Input-String ( 1 : i )
WITH NO ADVANCING
END-IF
END-IF
I'd put those "legs" into paragraphs and PERFORM them, but the effect is the same.
GOBACK.
GOBACK
.
In the PROCEDURE DIVISION I only code full-stops/periods at the end of a label or SECTION or on a line of their own. When moving code about or inserting new code, you never have to concern yourself with moving a full-stop/period.
I'd also do something slightly different which has a bigger impact.
The way you have coded it, if the length of the string is OMITTED, then the CALLing program must supply and identifier of 255 bytes. If it does not, then your CALLed program will be picking up stuff it shouldn't.
If that is what you intend, then OK. If not, I'd consider not making the length optional, and using the length for the actual field, with OCCURS DEPENDING ON
.
01 LS-Input-String.
05 FILLER OCCURS 0 TO 255 TIMES
DEPENDING ON LS-Input-Length.
10 FILLER PIC X.
01 LS-Input-Length PIC 9(3).
...
MOVE LS-Input-Length TO Len
Now, when you have a zero-length input,
DISPLAY LS-Input-String
Is doing it more like you want. A new line, but not even a space on the old line.
Upvotes: 3
Reputation: 10553
In Cobol, the calling program is compiled completely separately from the called module, there are no header files like in C. So when compiling the calling program, the Compiler does not know the format of the parameters of the program being called. The Cobol Compiler will format parameters based on a set of rules it has. The format the Cobol Compiler decides on could be different from what the calling program is expecting.
So when in doubt, use a variable on the call
In your case, I suspect
CALL 'Display-String' USING WS-My-String, '010', 'F'
would work
Upvotes: 2