Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations IamaSherpa on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Microfocus - values on file description 3

Status
Not open for further replies.

fredericofonseca

IS-IT--Management
Jun 2, 2003
3,324
PT
Hi all,

Company I am at the moment is doing a migration from MF version 2.2 to 5.1 and we come across one particular problem which im posting below. If anyone had had this experience and has been able to solve it with some compiler/runtime directive it would be great if I could have it.

Old environment
OS - HP UX 64b
MF compiler - Micro Focus Server Express V2.2 revision 000

New
OS - AIX 6.1
MF compiler - Micro Focus Server Express V5.1 revision 000

All programs in both cases being compiled and run in 32bit mode

Problem
Some programs have file descriptions for extracts with values on the record as follows.
FD FILE1-OUT-FILE.
01 FILE1-OUT-REC.
03 FILE1-OUT-POLICY PIC X(12).
03 FILE1-OUT-1 PIC X(1) VALUE ';'.
03 FILE1-OUT-PREM PIC 9(15).9(02).
03 FILE1-OUT-2 PIC X(1) VALUE ';'.

When running on HP the the records are written to the file with the ";" on it.
On AIX the same program does not keep the ";" and replaces it with spaces.

I am fully aware that according to MF manuals these values on the FD are invalid and therefore compiler version dependent, meaning that the correct thing to do would be to change the program to write from a WS group field instead, but if there is a solution that does not imply code changes it would be better at this stage.


Program code
Code:
       IDENTIFICATION DIVISION.
       PROGRAM-ID.                               FILE1.
       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
             SELECT FILE1-OUT-FILE  ASSIGN TO "file1.out"
                 ORGANIZATION IS LINE SEQUENTIAL.
       DATA DIVISION.
       FILE SECTION.
       FD FILE1-OUT-FILE.
       01 FILE1-OUT-REC.
          03  FILE1-OUT-POLICY              PIC X(12).
          03  FILE1-OUT-1                   PIC X(1) VALUE ';'.
          03  FILE1-OUT-PREM                PIC 9(15).9(02).
          03  FILE1-OUT-2                   PIC X(1) VALUE ';'.
       WORKING-STORAGE SECTION.
       PROCEDURE DIVISION.
       000-START-SECTION.
      *====================
           OPEN OUTPUT FILE1-OUT-FILE.
           MOVE "1234" TO  FILE1-OUT-POLICY.
           WRITE FILE1-OUT-REC.
           CLOSE FILE1-OUT-FILE.
           GOBACK.

Program output AIX
Code:
1234
Program output HP
Code:
1234        ;                  ;


directives used - AIX
Code:
* Micro Focus Server Express         V5.1 revision 000 24-Feb-11 11:48 Page   1
* file1.cbl
* Directives File: cobol.dir
* Accepted - showdir
* Accepted - settings
* Accepted - ibmcomp
* Accepted - outdd
* Accepted - spzero
* Accepted - trace
* Accepted - foldcopyname"lower"
* Rejected - filecase
* Accepted - list()
* End Of Directives File: cobol.dir
* Setting: NOACCEPTREFRESH NOACU NOADV ALIGN"8" ALPHASTART"1" ALTER NOAMODE
*          NOANIM NOANIMPREP ANS85 NOAPOST NOAREACHECK ARITHMETIC"MF" ASSIGN
*          "DYNAMIC" NOASSIGN-PRINTER NOAUTOLOCK NOBELL BOUND NOBRIEF NOBS2000
*          BWZSTAR NOBYTEMODEMOVE CALLFH"EXTFH" NOCALLMCS NOCALLRECOVERY
*          CALLSORT"EXTSM" CANCEL CANCELLBR NOCHANGEMESSAGE CHARSET"ASCII"
*          CHECKDIV"ANSI" NOCHECKREFMOD NOCICS CICS-CPY NOCICSOPTIMIZE NOCMPR2
*          NOCOBFSTATCONV NOCOBIDY NOCOBOL370 COBOLDIR NOCOMP COMP-5"2" COMP-6
*          "2" NOCOMS85 NOCONFIRM NOCONVERTRET CONVSPACE COPYEXT",cbl,cpy"
*          NOCOPYLBR COPYLIST COPYLISTCOMMENT"1" NOCSI CURRENCY-SIGN"36"
*          CURRENT-DATE"MMDDYY" NODATA DATACOMPRESS"0" NODATA-CONTEXT DATE
*          DBCHECK DBCS"3" NODBCSSOSI DBSPACE DE-EDIT"2" DEFAULTBYTE"32"
*          NODEFAULTCALLS DETECTLOCK NODG DIALECT"MF" NODIRECTIVES-IN-COMMENTS
*          NODOSVS NODPCINSUBSCRIPT DYNAM NOEARLY-RELEASE ECHO NOECHOALL
*          NOEDITOR ENSUITE"0" NOENTCOBOL ERRFORMAT"1" ERRLIST"EMBED" NOERRQ
*          FASTSORT NOFCD3 NOFCDREG NOFDCLEAR NOFILESHARE FILETYPE"0" NOFLAG
*          NOFLAGAS NOFLAGCD NOFLAGEUC NOFLAGMIG NOFLAGQ FLAGSINEDIT NOFLAGSTD
*          NOFOLDCALLNAME FOLDCOPYNAME"LOWER" FORM"60" NOFP-ROUNDING
*          NOHOSTARITHMETIC NOHOST-NUMCOMPARE NOHOST-NUMMOVE NOHOSTFD NOIBM-MS
*          IBMCOMP IDXFORMAT"0" NOILGEN IMPLICITSCOPE NOINDD INFORETURN"0"
*          NOINITCALL INT"file1.int" INTDATE"ANSI" INTLEVEL"2" IOCONV
*          NOISO2002 NOIXNLSKEY NOIXNUMKEY KEEP-INT KEYCHECK KEYCOMPRESS"0"
*          NOLIBRARIAN NOLINE-COUNT LIST"file1.lst" LISTPATH"" LISTWIDTH"80"
*          LITVAL-SIZE"4" LOCKTYPE"0" NOMAPNAME NOMAXERROR METHODDEFAULT
*          "REFERENCE" MF"13" MFCOMMENT NOMOVELENCHECK NOMS NOMVS NATIVE
*          "ASCII" NONATIVEFLOATINGPOINT NONCHAR NONEWBASENAME NONLS NSYMBOL
*          "DBCS" NOODOOSVS NOODOSLIDE NOOLDBLANKLINE NOOLDCOPY NOOLDINDEX
*          NOOLDNEXTSENTENCE NOOLDREADINTO NOOLDSTRMIX OOCTRL
*          "-C-E-G-P+Q+R-S+W" OPTIONAL-FILE NOOS390 OSEXT"" NOOSVS OUTDD
*          "SYSOUT 132 L" NOP64 NOPANVALET PERFORM-TYPE"MF" NOPREPLIST
*          NOPREPROCESS NOPRINT-EXT NOPROFILE NOPROGID-COMMENT
*          NOPROGID-INT-NAME NOPROTECT-LINKAGE PROTOTYPE"RELAXED" QUAL
*          QUALPROC NOQUERY QUOTE NORAWLIST NORDW RECMODE"F" NOREENTRANT NOREF
*          NOREFNO REMAINDER"1" REPORT-LINE"256" RESEQ NORETRYLOCK REWRITE-LS
*          NORM RTNCODE-SIZE"4" NORWHARDPAGE NOSAA SEG NOSEQCHK SEQUENTIAL
*          "RECORD" NOSERIAL SETTING"LINE" NOSHAREOUTDD SHOW-DIR SIGN"ASCII"
*          NOSIGNFIXUP SORTTYPE"DFSORT" SOURCEFORMAT"FIXED" SOURCETABSTOP"8"
*          SPZERO NOSSRANGE STDERR NOSTICKY-LINKAGE NOSTICKY-PERFORM SUPFF
*          SWITCHTYPE"1" SYMBSTART"1" SYSPUNCH"132" TERMPAGE TIME TRACE TRUNC
*          "ANSI" NOTRUNCCALLNAME NOTRUNCCOPY TRUNCINC"10" UNICODE"NATIVE"
*          NOVERBOSE NOVSC2 WARNING"1" NOWB NOWB2 NOWB3 WEBSERVER"CGI"
*          NOWRITELOCK NOWRITETHRU NOXOPEN NOXREF NOZEROLENGTHFALSE NOZEROSEQ
*          NOZWB
directives used - HP
Code:
Micro Focus Server Express         V2.2 revision 000 24-Feb-11 11:13 Page   1
* file1.cbl
* Directives File: cobol.dir
* Accepted - showdir
* Accepted - settings
* Accepted - ibmcomp
* Accepted - outdd
* Accepted - spzero
* Accepted - trace
* Accepted - foldcopyname"lower"
* Rejected - filecase
* Accepted - list()
* End Of Directives File: cobol.dir
* Setting: NOACCEPTREFRESH NOADV ALIGN"8" ALPHASTART"1" ALTER NOANIM
*          NOANSI2000 ANS85 NOAPOST NOAREACHECK ARITHMETIC"MF" ASSIGN"DYNAMIC"
*          NOASSIGN-PRINTER NOAUTOLOCK NOBELL BOUND NOBRIEF NOBS2000 NOBWZSTAR
*          NOBYTEMODEMOVE CALLFH"EXTFH" NOCALLMCS NOCALLRECOVERY CALLSORT
*          "EXTSM" CANCELLBR NOCHANGEMESSAGE CHARSET"ASCII" CHECKDIV"ANSI"
*          NOCICS CICS-CPY NOCICSOPTIMIZE NOCMPR2 NOCOBFSTATCONV NOCOBIDY
*          NOCOBOL370 COBOLDIR NOCOMP COMP-5"2" COMP-6"2" NOCOMS85 NOCONFIRM
*          NOCONVERTPTR NOCONVERTRET CONVSPACE COPYEXT",cbl,cpy" NOCOPYLBR
*          COPYLIST NOCSI CURRENCY-SIGN"36" CURRENT-DATE"MMDDYY" NODATA
*          DATACOMPRESS"0" NODATA-CONTEXT DATE DBCHECK DBCS"3" NODBCSSOSI
*          DBSPACE DE-EDIT"2" DEFAULTBYTE"32" NODEFAULTCALLS DETECTLOCK NODG
*          DIALECT"MF" NODIRECTIVES-IN-COMMENTS NODOSVS NODPCINSUBSCRIPT DYNAM
*          NOEARLY-RELEASE ECHO NOECHOALL NOEDITOR ENSUITE"0" ERRLIST"EMBED"
*          NOERRQ FASTSORT NOFCD3 NOFCDREG NOFDCLEAR NOFILESHARE FILETYPE"0"
*          NOFLAG NOFLAGAS NOFLAGCD NOFLAGEUC NOFLAGMIG NOFLAGQ FLAGSINEDIT
*          NOFLAGSTD NOFOLDCALLNAME FOLDCOPYNAME"LOWER" FORM"60" NOFP-ROUNDING
*          NOHOST-NUMCOMPARE NOHOST-NUMMOVE NOHOSTFD NOIBM-MS IBMCOMP
*          IDXFORMAT"0" IMPLICITSCOPE NOINDD INFORETURN"0" NOINITCALL INT
*          "file1.int" INTDATE"ANSI" INTLEVEL"2" IOCONV NOISO2000 NOIXNLSKEY
*          NOIXNUMKEY KEEP-INT KEYCHECK KEYCOMPRESS"0" NOLIBRARIAN
*          NOLINE-COUNT LIST"file1.lst" LISTPATH"" LISTWIDTH"80" LITVAL-SIZE
*          "4" LOCKTYPE"0" NOMAPNAME NOMAXERROR MF"12" MFCOMMENT
*          NOMOVELENCHECK NOMS NATIVE"ASCII" NONCHAR NONESTCALL NONLS
*          NOODOOSVS NOODOSLIDE NOOLDBLANKLINE NOOLDCOPY NOOLDINDEX
*          NOOLDNEXTSENTENCE NOOLDREADINTO NOOLDSTRMIX OOCTRL
*          "-C-E-G-P+Q+R-S-W" OPTIONAL-FILE OSEXT"" NOOSVS OUTDD
*          "SYSOUT 132 L A" NOP64 NOPANVALET PERFORM-TYPE"MF" NOPREPLIST
*          NOPREPROCESS NOPRINT-EXT NOPROFILE NOPROGID-COMMENT
*          NOPROTECT-LINKAGE PROTOTYPE"RELAXED" QUAL QUALPROC NOQUERY QUOTE
*          NORAWLIST NORDEFPTR NORDW RECMODE"F" NOREENTRANT NOREF NOREFNO
*          REMAINDER"1" REPORT-LINE"256" RESEQ NORETRYLOCK REWRITE-LS NORM
*          NORNIM RTNCODE-SIZE"4" NORWHARDPAGE NOSAA SEG NOSEQCHK SEQUENTIAL
*          "RECORD" NOSERIAL SETTING"LINE" SHOW-DIR SIGN"ASCII" SOURCEFORMAT
*          "FIXED" SPZERO NOSSRANGE STDERR NOSTICKY-LINKAGE NOSTICKY-PERFORM
*          SUPFF SYMBSTART"1" TERMPAGE TIME TRACE TRUNC"ANSI" NOTRUNCCALLNAME
*          NOTRUNCCOPY NOVERBOSE NOVSC2 WARNING"1" NOWB NOWB2 NOWB3 WEBSERVER
*          "CGI" NOWRITELOCK NOWRITETHRU NOXOPEN NOXREF NOZEROLENGTHFALSE
*          NOZEROSEQ NOZWB


Regards

Frederico Fonseca
SysSoft Integrated Ltd

FAQ219-2884
FAQ181-2886
 
I doubt there is any way to avoid code changes. As you said, using values in the record descriptions in the File Section is illegal. You must be aware that depending on the version of the compiler, the OS, and various source code options, these areas may not even have memory allocated to them until the file is open, or sometimes only during processing the Write statement.
 
NF have fixed quite some bugs of older compilers in the 5.0/5.1 toolchain. This must be one of the issues they fixed :)
 
FF,

have no experience with MF ServerExpress and its configuration to be able to help, but in terms of adding code, I would think that a minimal INITIALIZE statement of the FD record name prior to loading values (quite possibly even a single initialize at the beginning of program, or perhaps after file is OPEN'ed), would suffice to ensure that these static value fields are properly populated.

So, to use the example you give, the code would change as follows:
Code:
           OPEN OUTPUT FILE1-OUT-FILE.
           [red]INITIALIZE FILE1-OUT-REC.[/red]
           MOVE "1234" TO  FILE1-OUT-POLICY.
           WRITE FILE1-OUT-REC.

Code what you mean,
and mean what you code!
But by all means post your code!

Razalas
 
Razalas,

that was one of the options I considered, but it doesn't work either. Would mean less coding changes.

Unfortunately unless MF comes back with a solution we will need to move all these records layouts to WS and change programs to do a WRITE REC FROM WS-REC.
Nothing major really compared to one of our other issues. We currently having a much bigger issue with some differences on how spaces on numeric fields are handled, but not even posting that one here. Really hate when lazy programmers don't initialize their variables.

Regards

Frederico Fonseca
SysSoft Integrated Ltd

FAQ219-2884
FAQ181-2886
 
As a note, back in '76 my boss had written a program with similar illegal code. When I had to make a change to it, I told him the code was illegal. He said it made him "feel good" to have it in the program. I told him that some day it would bite him. It was about two years later a change to the O/S did just that, and I had to change the program to remove the code.
 
Frederico,

Just looking at the documentation, may I suggest a slightly different INITIALIZE statement?
Code:
           OPEN OUTPUT FILE1-OUT-FILE.
           INITIALIZE FILE1-OUT-REC [COLOR=red]to VALUE[/color].
           MOVE "1234" TO  FILE1-OUT-POLICY.
           WRITE FILE1-OUT-REC.

As you are aware from my background, I have no actual experience with this particular compiler, but that is what the VALUE clause is designed to do. Perhaps it will work in this situation (and give you the 'less coding' option), assuming the compiler didn't just toss the VALUE literals because they were in the FILE SECTION.

One very practical reason to be permissive about VALUE clauses in FILE SECTION data item definitions is to allow a single copybook to be used to define record areas in all the sections of the DATA DIVISION without a bunch of nagging error messages.

Tom Morrison
Micro Focus
 
Hi Tom,

How things?

Yes that might work. Forgot MF had that option. Will test it later on

Pitty you ain't on the MF side of it. One test case I posted on microfocus forum would most likely be interesting to you.


Frederico

Regards

Frederico Fonseca
SysSoft Integrated Ltd

FAQ219-2884
FAQ181-2886
 
Just confirmed and the INITIALIZE .. TO VALUE works as suspected

For information to others the following is also required if the record contains FILLER fields with values

INITIALIZE xxx WITH FILLER TO VALUE



Regards

Frederico Fonseca
SysSoft Integrated Ltd

FAQ219-2884
FAQ181-2886
 
I am glad that this works.

I have been working with Visual COBOL a bit, and have several members of my team working on different aspects of it. But that does not really mean that I can say with certainty about the previous Micro Focus products.

RM put in the INITIALIZE some time ago, and we had it in several examples for various products. I like it...

Good to 'talk' with you again.

Tom Morrison
Micro Focus
 
by using special features of any cobol compiler, the source will not be portable without conversion to an other platform.

Is this really what your customer wants, to be tied to Microfocus?
 
Big companies like this one won't change compiler that easily. But this particular functionality is now accepted by almost all if not all current cobol compilers.

But even without this one, other functions that have already been widely spread would make it very hard to port to any other compiler.

Regards

Frederico Fonseca
SysSoft Integrated Ltd

FAQ219-2884
FAQ181-2886
 
yeah, there are other compilers... realy...

For example IBM's mainframe COBOL compiler that still has a feature that is over 30 years old en that is still not implemented anywhere.... as far as i know....

It is about multiple occurs depending on in one structure.....

An other thing in pc-environment which prevents a lot of development in COBOL is the price and the costs of the runtime system....

So yes, it is like an old Pascal compiler once.... it costed as much as 6000 guilder or something like that... high quality but far too much.... Borland bought the pascal-compiler company and sold the compiler for 200 guilder.... and everybody bought that compiler...it made Borland big at that time... If you want to buy a MF compiler... i guess it is about 22000 guilder.... or 10000 euro or so... and no royalty free runtime.... so... in all those years it seems that nobody learned what good was about the Borland effect.... :-(
 
Microfocus is now, at least in some os'es, 15 or 30k per cpu CORE for the runtime and a significant amount for development license, also per core and per user

Regards

Frederico Fonseca
SysSoft Integrated Ltd

FAQ219-2884
FAQ181-2886
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top