[Search for users] [Overall Top Noters] [List of all Conferences] [Download this site]

Conference csc32::cobol2

Title:Micro Focus Cobol/2
Notice:See note 10 for instructions on BUG reports
Moderator:CSC32::E_VAETH
Created:Sat Jan 19 1991
Last Modified:Wed Jun 04 1997
Last Successful Update:Fri Jun 06 1997
Number of topics:577
Total number of notes:1843

566.0. "MOVE PIC X(30) TO PIC X(28)B unpredictable results" by UTRTSC::VELDMAN () Mon Mar 24 1997 02:16

Hello,

I have the following strange problem :

Versions:
=========
Digital UNIX V3.2g + Micro Focus Cobol V4.0 revision 16 

Programname xxx.cob

Output is different with 'cobrun xxx.int' 'cobrun xxx.gnt' or 'xxx'

'cobrun xxx.int' gives (as expected)

--------
Begin
 
         123456789012345678901234567890		(This is veld-30)
 
         1234567890123456789012345678		(This is veld-28)
 
End
--------

'cobrun xxx.gnt' and 'xxx' gives the following:

--------

Begin
 
         123456789012345678901234567890		(This is veld-30)
 
         124567890123456789012345678		(This is veld-28)
 
End
--------

Position 3 seems to have lost it's contents, and position 28 is gone also.....

When we omit the B (in PIC X(28)B), the output is OK.

The sample code that is responsible for this output:

000100*****************************************************************
000200 IDENTIFICATION DIVISION.
000300*----------------------------------------------------------------
000400 PROGRAM-ID.  		ruud.
000500 AUTHOR.	                     	ZCS - InfoSystems.
000600 INSTALLATION.            	B20.
000700 DATE-WRITTEN.            	maart 1997.
000800 DATE-COMPILED.
000900*
001200*
001300*****************************************************************
001400 ENVIRONMENT DIVISION.
001500*----------------------------------------------------------------
001600 CONFIGURATION SECTION.
001700 SOURCE-COMPUTER.      	B20.
001800 OBJECT-COMPUTER.       	B20.
001900 SPECIAL-NAMES.             	DECIMAL-POINT IS COMMA.
002000*----------------------------------------------------------------
002100 INPUT-OUTPUT SECTION.
002200 FILE-CONTROL.
002300     SELECT VERSLAG          ASSIGN TO "farfak.vsl"
002400                     ORGANIZATION IS LINE SEQUENTIAL.
002500*****************************************************************
002600 DATA DIVISION.
002700*****************************************************************
002800 FILE SECTION.
002900*
003000 FD  VERSLAG.
003100 01  REGEL              PIC X(132).
003200*****************************************************
003300*----------------------------------------------------
003400 WORKING-STORAGE SECTION.
003500*----------------------------------------------------
003600 01  WS-PROGRAMMA-NAAM   PIC X(04) VALUE "RUUD".
003700*----------------------------------------------------
003800*
003900 01	 VELD-A.
004000     03  VELD-05         PIC X(05).
004100     03  VELD-30         PIC X(30).
004200     03  VELD-03         PIC X(03).
004300*
004400 01	 VELD-BX.
004500     03  VELD-B          PIC X(50).
004600     03  WS-DET REDEFINES VELD-B.
004700         05  VELD-C.
004800             07  FILLER  PIC X(05).
004900             07  VELD-28 PIC X(28)B.
005000             07  REST    PIC X(16).
005100     03  FILLER          PIC X(05).
005200*
012300 PROCEDURE DIVISION.
012400*****************************************************
012500 H00-HOOFD SECTION.
012600*****************************************************
012700 H00-00.
012800     DISPLAY SPACES UPON CRT.
012900     DISPLAY "Begin"  AT 0501.
013000*
013100     MOVE "AAAAA" TO VELD-05.
013200     MOVE "123456789012345678901234567890" TO VELD-30.
013300     MOVE "BBB" TO VELD-03.
013400*
013500     MOVE SPACES  TO VELD-B.
013600     MOVE VELD-30 TO VELD-28.
013600*
013800     DISPLAY VELD-30 AT 1010.
013900     DISPLAY VELD-28 AT 1210.
014000*
014100 H00-90.
014200     DISPLAY "End" AT 1501.
014300*
014400 H00-99.
014500     STOP RUN.
014600*
-----------------------------------------------------------------

Does anybody have a clue?

Regards,


Jelle Veldman - Digital UNIX Software Support
T.RTitleUserPersonal
Name
DateLines
566.1working itCSC32::E_VAETHSuffering from temporary brain cramp, stay tunedMon Mar 24 1997 21:494
    I see what you are seeing.  I don't know what the expected behavior is
    at this point.  I'll see if I can find out.
    
    -elin
566.2could be a bugCSC32::E_VAETHSuffering from temporary brain cramp, stay tunedSat Mar 29 1997 00:035
    From what I can tell, it looks as though Micro Focus COBOL is not doing
    the right thing.  Please submit a PDR per the instructions I emailed to
    you.