MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

SOC4 - Difference between COBOL 39O and Enterprise COBOL

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Application Programming
View previous topic :: View next topic  
Author Message
coolman
Intermediate


Joined: 03 Jan 2003
Posts: 283
Topics: 27
Location: US

PostPosted: Tue Oct 17, 2006 12:18 pm    Post subject: SOC4 - Difference between COBOL 39O and Enterprise COBOL Reply with quote

Hello,

My program is given below - When I compile it using COBOL 390 it works even though the subscript reaches -60 , whereas when I compile it in eCobol it abends with SOC4

I've printed out the compile options for both compilers in effect and tried to do a match and they are identical and so are the LE options in effect - What could be the problem?

One wild guess is that the program is getting loaded in the memory is different locations in both cases. But I can't prove it or may be I'm totally clueless

Please suggest.


Code:

       IDENTIFICATION DIVISION.                                         
       PROGRAM-ID.    SAMPLE                                           
       DATE-COMPILED.                                                   
       ENVIRONMENT DIVISION.                                           
       DATA DIVISION.                                                   
       WORKING-STORAGE SECTION.                                         
       01 W-SUB                     PIC S9(04) COMP VALUE 0.           
       01 WS-VARS.                                                     
           05  LPART-INDEX              PIC S9(4) COMP   VALUE ZEROS.   
           05  WS-LAST-PART-LENGTH      PIC X(60) VALUE SPACES.         
           05  WS-TXT-LENGTH            PIC X(25) VALUE SPACES.         
016800     05  USER-AREA-TXT          PIC X(25) VALUE SPACES.           
       01 T-INTERNAL-TABLE-AREA.                                       
           05 INTERNAL-TABLE        OCCURS 6 TIMES                     
                                    ASCENDING KEY IS  T-CODE           
                                    INDEXED BY CR-INDEX.               
              10  T-CODE              PIC  X(01).                       
              10  T-AMT               PIC  9(09).                       
       PROCEDURE DIVISION.                                             
            MOVE LOW-VALUES                                             
                                            TO WS-TXT-LENGTH
PERFORM VARYING LPART-INDEX FROM                           
               LENGTH OF WS-TXT-LENGTH BY -1               
             UNTIL WS-TXT-LENGTH (LPART-INDEX:1) > SPACES   
END-PERFORM                                                 
DISPLAY 'LPART-INDEX ' LPART-INDEX                         
MOVE WS-TXT-LENGTH (1:LPART-INDEX) TO                       
                            USER-AREA-TXT (1:LPART-INDEX). 
STOP RUN.                                                   


________
Lincoln L-head V12 engine picture


Last edited by coolman on Sat Feb 05, 2011 1:53 am; edited 1 time in total
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12375
Topics: 75
Location: San Jose

PostPosted: Tue Oct 17, 2006 1:10 pm    Post subject: Reply with quote

Quote:

I've printed out the compile options for both compilers in effect and tried to do a match and they are identical and so are the LE options in effect - What could be the problem?


Coolman,

start reading this topic from here and see if all the LE options are the same.

http://www.mvsforums.com/helpboards/viewtopic.php?p=33730#33730

Hope this helps..

Cheers

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
coolman
Intermediate


Joined: 03 Jan 2003
Posts: 283
Topics: 27
Location: US

PostPosted: Tue Oct 17, 2006 1:14 pm    Post subject: Reply with quote

Kolusu,

I've already seen this post earlier - In this case, the situation is not between test and prod as in the illustrated post - Both of them are run in the identical region with the same LE libs - The only change I do the JCL is to change the STEPLIB for IGYCRCTL from COBOL390 lib to eCobol lib. That's it. This causes the abend.
________
herbal vaporizers


Last edited by coolman on Sat Feb 05, 2011 1:54 am; edited 1 time in total
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12375
Topics: 75
Location: San Jose

PostPosted: Tue Oct 17, 2006 1:17 pm    Post subject: Reply with quote

coolman,

Did the COBOl390 have the Compiler option SSRANGE ?

Take the example posted in the other thread and run it with different steplibs and see if they abend.

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
coolman
Intermediate


Joined: 03 Jan 2003
Posts: 283
Topics: 27
Location: US

PostPosted: Tue Oct 17, 2006 1:28 pm    Post subject: Reply with quote

Kolusu,

No, It did NOT - BTW, If you have looked at the procedure division, no table is being used -So, why should I use SSRANGE here - That table in the working storage was one of my old programs (as you can see, I dont' use it in the procedure division) - All it does is referential subscripting, should I use SSRANGE for that too?
________
vaporgenie


Last edited by coolman on Sat Feb 05, 2011 1:54 am; edited 1 time in total
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12375
Topics: 75
Location: San Jose

PostPosted: Tue Oct 17, 2006 1:33 pm    Post subject: Reply with quote

coolman,

Yes you need the SSRANGE parm. read the following

Code:

SSRANGE specifies that the generated code is to check to  ensure
that:                                                           
                                                                 
    -the effective address generated for an index  or  subscript
     does  not  reference  an  area  outside  the  region of the
     associated  table                                           
    -the  current  effective  length  for a variable-length item
     (i.e.,  OCCURS DEPENDING ON) is no greater than its maximum
     defined length                                             
    -for reference modification expressions:                     
                                                                 
            -the reference modification starting position is  no
             less  than 1 and no greater than the current length
             of the subject item                                 
            -the  reference  modification   length   value   (if
             specified) is no less than 1                       
            -the  reference  modification  starting position and
             length value (if specified)  do  not  reference  an
             area  that  extends  beyond  the end of the subject
             item                                               
                                                                 
If an "out of range" condition is  detected,  an  error  message
will  be  written  to  write-to-programmer  route code 11 (i.e.,
usually the SYSPRINT dd  statement)  and  the  program  will  be
terminated.  When running under CICS, these messages are written
to a temporary storage queue.                                   
                                                                 
The SSRANGE option can result in some performance degradation.   
                                                                 
The  NOSSRANGE  run time  option can be specified at run time in
order to inhibit the range checking code generated by specifying
SSRANGE as as a compile time option.  In this way, the "dormant"
range checking code can be  activated  at  run  time  (i.e.,  to
assist  in  resolving  any  unexpected errors) without having to
recompile.                                                       


Hope this helps...

Cheers

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
coolman
Intermediate


Joined: 03 Jan 2003
Posts: 283
Topics: 27
Location: US

PostPosted: Tue Oct 17, 2006 1:34 pm    Post subject: Reply with quote

Kolusu,

However, I did as you had suggested using SSRANGE even for variable that are not arrays and it works as expected.

For the COBOL/390 compilation - I added CBL SSRANGE and set the CHECK(ON) LE option and it abended with U4038

For the eCOBOL, without me having to set any of these two options, the program is abending with SOC4.

now, without having to change the code, is there a way that I can make the eCobol compiled work just as it's OS/390 counterpart
________
Daihatsu Midget


Last edited by coolman on Sat Feb 05, 2011 1:54 am; edited 1 time in total
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12375
Topics: 75
Location: San Jose

PostPosted: Tue Oct 17, 2006 1:52 pm    Post subject: Reply with quote

coolman,

Quote:

For the eCOBOL, without me having to set any of these two options, the program is abending with SOC4.


Your shop must have modified default compiler options and added the SSRANGE compiler option as default option. So talk to your system programmers and see if there was a reason for that compiler option

Quote:

now, without having to change the code, is there a way that I can make the eCobol compiled work just as it's OS/390 counterpart


Techincally you are not changing any code in the program , all you are doing is adding the compiler overrides at the top of the program. Even if that is considered as code change then you need to change the compile JCL

Code:

//STEP0100 EXEC PGM=IGYCRCTL,PARM='NOSSRANGE'   


Hope this helps...

Cheers

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
coolman
Intermediate


Joined: 03 Jan 2003
Posts: 283
Topics: 27
Location: US

PostPosted: Tue Oct 17, 2006 2:02 pm    Post subject: Reply with quote

Kolusu,

I have cut pasted the ecobol compiler options in effect below - How do you say the option SSRANGE was in effect? Also, if it was in effect, the range checking would not be performed if I don't have CHECK(ON) during runtime - Assume, I have everything as you say, I would still get the message below and not S0C4

Quote:

IGZ0072S A reference modification start position value of 0 on line
000025 referenced an area outside the region of data item
WS-TXT-LENGTH.


Code:

PP 5655-G53 IBM Enterprise COBOL for z/OS  3.4.0                         
Options in effect:                                                         
    NOADATA                                                               
    NOADV                                                                 
      QUOTE                                                               
      ARITH(COMPAT)                                                       
      AWO                                                                 
      BUFSIZE(28672)                                                       
    NOCICS                                                                 
      CODEPAGE(1140)                                                       
    NOCOMPILE(E)                                                           
    NOCURRENCY                                                             
      DATA(31)                                                             
    NODATEPROC                                                             
    NODBCS                                                                 
    NODECK                                                                 
    NODIAGTRUNC                                                           
    NODLL                                                                 
NODUMP                                                 
  DYNAM                                               
NOEXIT                                                 
NOEXPORTALL                                           
NOFASTSRT                                             
  FLAG(I,E)                                           
NOFLAGSTD                                             
  INTDATE(ANSI)                                       
  LANGUAGE(EN)                                         
  LIB                                                 
  LINECOUNT(60)                                       
  LIST                                                 
  MAP                                                 
NOMDECK                                               
NONAME                                                 
  NSYMBOL(DBCS)                                       
NONUMBER                                               
  NUMPROC(MIG)                                         
   OBJECT                     
 NOOFFSET                     
   OPTIMIZE(STD)             
   OUTDD(SYSOUT)             
   PGMNAME(COMPAT)           
   RENT                       
   RMODE(AUTO)               
 NOSEQUENCE                   
   SIZE(MAX)                 
   SOURCE                     
   SPACE(1)                   
 NOSQL                       
NOSSRANGE   ==> IT'S ALREADY THERE
   TERM                       
 NOTEST                       
 NOTHREAD                     
   TRUNC(OPT)                 
 NOVBREF                     
NOWORD                     
  XREF(FULL)               
  YEARWINDOW(1900)         
  ZWB         



FYI, I tried coding the parm (NOSSRANGE) for the eCobol compilation even if it's already in effect and as expected, it abended with S0C4. I still feel that it's got to do with the program getting loaded differently
________
launch box vaporizer


Last edited by coolman on Sat Feb 05, 2011 1:54 am; edited 1 time in total
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12375
Topics: 75
Location: San Jose

PostPosted: Tue Oct 17, 2006 2:23 pm    Post subject: Reply with quote

I just ran the piece of code you have shown in your first post. It completed with return code zero. The compiler option is NOSSRANGE

Here is the JCL I used to run your program.

Code:

//STEP0100 EXEC PGM=IGYCRCTL                   
//STEPLIB  DD DSN=SYS1.SIGYCOMP,               
//            DISP=SHR                         
//SYSPRINT DD SYSOUT=*                         
//SYSTERM  DD SYSOUT=*                         
//SYSUT1   DD UNIT=DISK,SPACE=(CYL,(10,2),RLSE)
//SYSUT2   DD UNIT=DISK,SPACE=(CYL,(10,2),RLSE)
//SYSUT3   DD UNIT=DISK,SPACE=(CYL,(10,2),RLSE)
//SYSUT4   DD UNIT=DISK,SPACE=(CYL,(10,2),RLSE)
//SYSUT5   DD UNIT=DISK,SPACE=(CYL,(10,2),RLSE)
//SYSUT6   DD UNIT=DISK,SPACE=(CYL,(10,2),RLSE)
//SYSUT7   DD UNIT=DISK,SPACE=(CYL,(10,2),RLSE)
//SYSLIN   DD DSN=&&LOADSET,                   
//            DISP=(MOD,PASS),                 
//            UNIT=DISK,                       
//            SPACE=(CYL,(1,1),RLSE)           
//SYSIN    DD *                                                     
        IDENTIFICATION DIVISION.                                   
        PROGRAM-ID.    SAMPLE                                       
        DATE-COMPILED.                                             
        ENVIRONMENT DIVISION.                                       
        DATA DIVISION.                                             
        WORKING-STORAGE SECTION.                                   
        01 W-SUB                     PIC S9(04) COMP VALUE 0.       
        01 WS-VARS.                                                 
            05  LPART-INDEX          PIC S9(4) COMP  VALUE ZEROS.   
            05  WS-LAST-PART-LENGTH  PIC X(60) VALUE SPACES.       
            05  WS-TXT-LENGTH        PIC X(25) VALUE SPACES.       
            05  USER-AREA-TXT        PIC X(25) VALUE SPACES.       
                                                                   
        01 T-INTERNAL-TABLE-AREA.                                   
            05 INTERNAL-TABLE        OCCURS 6 TIMES                 
                                     ASCENDING KEY IS  T-CODE       
                                     INDEXED BY CR-INDEX.           
               10  T-CODE            PIC  X(01).                   
                 10  T-AMT           PIC  9(09).                   
                                                                   
        PROCEDURE DIVISION.                                         
             MOVE LOW-VALUES  TO WS-TXT-LENGTH                     
             PERFORM VARYING LPART-INDEX FROM                       
                     LENGTH OF WS-TXT-LENGTH BY -1                 
               UNTIL WS-TXT-LENGTH (LPART-INDEX:1) > SPACES         
                                                                   
             END-PERFORM                                           
                                                                   
             DISPLAY 'LPART-INDEX ' LPART-INDEX                     
             MOVE WS-TXT-LENGTH (1:LPART-INDEX) TO                 
                                     USER-AREA-TXT (1:LPART-INDEX).
                                                                   
             STOP RUN.                                             
                                           
//*                       
//STEP0200 EXEC PGM=LOADER,                 
//             PARM=('LIST,LET,XREF,DCBS,'),
//             COND=(5,LT,STEP0100)         
//SYSLIB   DD DSN=SYS1.SCEELKED,           
//            DISP=SHR                     
//SYSLIN   DD DSN=*.STEP0100.SYSLIN,       
//            DISP=(OLD,DELETE)             
//SYSOUT   DD SYSOUT=*                     
//SYSPRINT DD SYSOUT=*



Then I added the SSRANGE compiler option and the program abended with u4038

and sysprint had this message

Code:

IGZ0072S A reference modification start position value of 0 on line 000027
referenced an area outside the region of data item WS-TXT-LENGTH.

From compile unit SAMPLE at entry point SAMPLE at compile unit offset
+0000046A at entry offset +0000046A at address 175B746A.


So if your pgm is abending with S0c4 then it must be some other section of the program.

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
coolman
Intermediate


Joined: 03 Jan 2003
Posts: 283
Topics: 27
Location: US

PostPosted: Tue Oct 17, 2006 2:29 pm    Post subject: Reply with quote

Kolusu,

What does your IGYCRCTL point to? eCobol or OS/390 compiler steplibs? - If it's OS/390, it WOULD work and if it's eCobol it WOULD fail (atleast for me)

In my shop, I point my steplib to below for doing eCobol compiles

Code:


 //STEPLIB  DD DISP=SHR,DSN=SYS1.IGYECBL.SIGYCOMP   



Other than whatever I have shown, there's nothing else in that program. If needed, I can even put the compile JCL. It would be the same as yours except the STEPLIB dataset
________
digital vaporizer


Last edited by coolman on Sat Feb 05, 2011 1:54 am; edited 1 time in total
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12375
Topics: 75
Location: San Jose

PostPosted: Tue Oct 17, 2006 2:33 pm    Post subject: Reply with quote

If you look at my job, the steplib points to
Code:

//STEPLIB  DD DSN=SYS1.SIGYCOMP,               
//            DISP=SHR         


and yes we are running enterprise cobol.

Code:

PP 5655-G53 IBM Enterprise COBOL for z/OS  3.3.1           


Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
coolman
Intermediate


Joined: 03 Jan 2003
Posts: 283
Topics: 27
Location: US

PostPosted: Tue Oct 17, 2006 2:39 pm    Post subject: Reply with quote

Thanks for all the great responses, Kolusu - I guess I have hit a road block and am not sure why it's abending on my system but not yours.
________
VTR1000F


Last edited by coolman on Sat Feb 05, 2011 1:54 am; edited 1 time in total
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12375
Topics: 75
Location: San Jose

PostPosted: Tue Oct 17, 2006 2:43 pm    Post subject: Reply with quote

coolman,

try running the Job I posted as is(dont even change the steplib loadlib's) in this post

http://www.mvsforums.com/helpboards/viewtopic.php?p=34879#34879

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
coolman
Intermediate


Joined: 03 Jan 2003
Posts: 283
Topics: 27
Location: US

PostPosted: Tue Oct 17, 2006 3:09 pm    Post subject: Reply with quote

I'm getting a JCL Error as the STEPLIB dataset is not available - It's available at my shop as SYS1.IGY.SIGYCOMP (and contains the COBOL OS/390 compiler)
________
Toyota Liteace
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Application Programming All times are GMT - 5 Hours
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group