Re: Arithmetic on COBOL usage is pointer

2010-04-19 Thread Chase, John
> -Original Message-
> From: IBM Mainframe Discussion List On Behalf Of Kirk Talman
> 
> Also be aware that I recently shot a bug for a compatriot where having
an
> unsigned binary number defined made a If numeric fail.  never went to
root
> cause but it seemed there might be an issue of moves between binary
fields
> being handled by cobol using MVC instead of ZAP.

I doubt you'd really want to ZAP (Zero and Add Packed) a (numeric)
binary field -- for one, ZAP puts the sign on the wrong end of the field
(and uses more than one bit for the sign).

-jc-

> 
> GOKW
> 
> IBM Mainframe Discussion List  wrote on
04/16/2010
> 12:15:53 PM:
> 
> > From: "Chase, John" 
> > Date: 04/16/2010 12:16 PM
> > Subject: Re: Arithmetic on COBOL usage is pointer
> 
> > > -Original Message-
> > > From: IBM Mainframe Discussion List On Behalf Of Joe Reichman
> > >
> > > I redefined a usage pointer to PIC 9(8) comp to do arithmetic and
got
> > > weird results
> > > Are there any rules for doing math on
> > > Usage is pointer
> 
> > Compiler option TRUNC(BIN) would be "a friend", but specifying
COMP-5 on
> > your REDEFINE would be better.
> 
> > -jc-
> 
> 
> -
> The information contained in this communication (including any
> attachments hereto) is confidential and is intended solely for the
> personal and confidential use of the individual or entity to whom
> it is addressed. If the reader of this message is not the intended
> recipient or an agent responsible for delivering it to the intended
> recipient, you are hereby notified that you have received this
> communication in error and that any review, dissemination, copying,
> or unauthorized use of this information, or the taking of any
> action in reliance on the contents of this information is strictly
> prohibited. If you have received this communication in error,
> please notify us immediately by e-mail, and delete the original
> message. Thank you
> 
> --
> For IBM-MAIN subscribe / signoff / archive access instructions,
> send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
> Search the archives at http://bama.ua.edu/archives/ibm-main.html

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-19 Thread Kirk Talman
Also be aware that I recently shot a bug for a compatriot where having an 
unsigned binary number defined made a If numeric fail.  never went to root 
cause but it seemed there might be an issue of moves between binary fields 
being handled by cobol using MVC instead of ZAP.

GOKW

IBM Mainframe Discussion List  wrote on 04/16/2010 
12:15:53 PM:

> From: "Chase, John" 
> Date: 04/16/2010 12:16 PM
> Subject: Re: Arithmetic on COBOL usage is pointer

> > -Original Message-
> > From: IBM Mainframe Discussion List On Behalf Of Joe Reichman
> > 
> > I redefined a usage pointer to PIC 9(8) comp to do arithmetic and got
> > weird results
> > Are there any rules for doing math on
> > Usage is pointer

> Compiler option TRUNC(BIN) would be "a friend", but specifying COMP-5 on
> your REDEFINE would be better.

> -jc-


-
The information contained in this communication (including any
attachments hereto) is confidential and is intended solely for the
personal and confidential use of the individual or entity to whom
it is addressed. If the reader of this message is not the intended
recipient or an agent responsible for delivering it to the intended
recipient, you are hereby notified that you have received this
communication in error and that any review, dissemination, copying,
or unauthorized use of this information, or the taking of any
action in reliance on the contents of this information is strictly
prohibited. If you have received this communication in error,
please notify us immediately by e-mail, and delete the original
message. Thank you 

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-19 Thread Kirk Talman
I believe using USAGE COMP-5 removes all truncation issues.

IBM Mainframe Discussion List  wrote on 04/16/2010 
11:47:09 AM:

> From: David Andrews 
> Subject: Re: Arithmetic on COBOL usage is pointer

> On Fri, 2010-04-16 at 11:28 -0400, Joe Reichman wrote:
> > I redefined a usage pointer to PIC 9(8) comp to do arithmetic
> 
> Have you compiled with TRUNC(BIN)?

> David Andrews


-
The information contained in this communication (including any
attachments hereto) is confidential and is intended solely for the
personal and confidential use of the individual or entity to whom
it is addressed. If the reader of this message is not the intended
recipient or an agent responsible for delivering it to the intended
recipient, you are hereby notified that you have received this
communication in error and that any review, dissemination, copying,
or unauthorized use of this information, or the taking of any
action in reliance on the contents of this information is strictly
prohibited. If you have received this communication in error,
please notify us immediately by e-mail, and delete the original
message. Thank you 

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-19 Thread McKown, John
> -Original Message-
> From: IBM Mainframe Discussion List 
> [mailto:ibm-m...@bama.ua.edu] On Behalf Of David Andrews
> Sent: Monday, April 19, 2010 8:30 AM
> To: IBM-MAIN@bama.ua.edu
> Subject: Re: Arithmetic on COBOL usage is pointer
> 
> On Mon, 2010-04-19 at 09:06 -0400, McKown, John wrote:
> > MOVE LARGEST-INPUT-RECORD (UNSTRING-OFFSET:
> >LENGTH OF SMF30ID)
> >  TO SMF30ID
> 
> I dig now; you're moving the segments to a separate segment-defining
> record in order to gain field addressability.  Using pointers (and
> redefines) I'd address that ID segment directly:
> 
> 01  SMF30-ADDRVAL   COMPPIC 9(8). 
> 01  SMF30-ADDRPTR   REDEFINES SMF30-ADDRVALPOINTER.
> 01  SMF30-ID-ADDRVALCOMPPIC 9(8). 
> 01  SMF30-ID-ADDRPTRREDEFINES SMF30-ID-ADDRVAL POINTER.
> 
> IF (SMF30ION = 1) 
> COMPUTE SMF30-ID-ADDRVAL =   
> SMF30-ADDRVAL + SMF30IOF - 4.
> SET ADDRESS OF SMFREC-30-IDENTIFICATION TO
> SMF30-ID-ADDRPTR. 
> 
> I kinda like my way better, but as others have pointed out it 
> isn't all
> that future-proof.  Guess I should fix that if I ever have to 
> crack that
> code open again.
> 
> -- 
> David Andrews

That is a good way too. And more efficient due to not moving data around. I 
don't consider using SET WS-POINTER TO ADDRESS OF WS-VAR and SET ADDRESS OF 
LS-VAR TO WS-POINTER to be doing arithmetic on a pointer. Arithmetic on a 
pointer is defining a USAGE BINARY variable on top of a POINTER, then using the 
ADD and SUBTRACT verbs to manipulate it. That is no longer necessary.

--
John McKown 
Systems Engineer IV
IT

Administrative Services Group

HealthMarkets(r)

9151 Boulevard 26 * N. Richland Hills * TX 76010
(817) 255-3225 phone * (817)-961-6183 cell
john.mck...@healthmarkets.com * www.HealthMarkets.com

Confidentiality Notice: This e-mail message may contain confidential or 
proprietary information. If you are not the intended recipient, please contact 
the sender by reply e-mail and destroy all copies of the original message. 
HealthMarkets(r) is the brand name for products underwritten and issued by the 
insurance subsidiaries of HealthMarkets, Inc. -The Chesapeake Life Insurance 
Company(r), Mid-West National Life Insurance Company of TennesseeSM and The 
MEGA Life and Health Insurance Company.SM

 

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-19 Thread David Andrews
On Mon, 2010-04-19 at 09:06 -0400, McKown, John wrote:
> MOVE LARGEST-INPUT-RECORD (UNSTRING-OFFSET:
>LENGTH OF SMF30ID)
>  TO SMF30ID

I dig now; you're moving the segments to a separate segment-defining
record in order to gain field addressability.  Using pointers (and
redefines) I'd address that ID segment directly:

01  SMF30-ADDRVAL   COMPPIC 9(8). 
01  SMF30-ADDRPTR   REDEFINES SMF30-ADDRVALPOINTER.
01  SMF30-ID-ADDRVALCOMPPIC 9(8). 
01  SMF30-ID-ADDRPTRREDEFINES SMF30-ID-ADDRVAL POINTER.

IF (SMF30ION = 1) 
COMPUTE SMF30-ID-ADDRVAL =   
SMF30-ADDRVAL + SMF30IOF - 4.
SET ADDRESS OF SMFREC-30-IDENTIFICATION TO
SMF30-ID-ADDRPTR. 

I kinda like my way better, but as others have pointed out it isn't all
that future-proof.  Guess I should fix that if I ever have to crack that
code open again.

-- 
David Andrews
A. Duda and Sons, Inc.
david.andr...@duda.com

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-19 Thread McKown, John
> -Original Message-
> From: IBM Mainframe Discussion List 
> [mailto:ibm-m...@bama.ua.edu] On Behalf Of David Andrews
> Sent: Monday, April 19, 2010 7:55 AM
> To: IBM-MAIN@bama.ua.edu
> Subject: Re: Arithmetic on COBOL usage is pointer
> 
> On Fri, 2010-04-16 at 20:33 -0400, Clark Morris wrote:
> > The more interesting question is why use a
> > pointer when reference modification works well
> > for playing with the SMF30 records?
> 
> 'splainey?  (That was the first COBOL I'd written in a very long time,
> and I was delighted to find pointers at all.  If there's a 
> better way to
> handle SMF30 records I'm all ears.)
> 
> -- 
> David Andrews

I use "Reference Modification" and not pointers.

You'll need to accept that I have all the proper WORKING STORAGE definitions as 
posting them for this would be too large. But in my code, I have something like:

 IF SMF30ION IS NOT EQUAL TO ZERO THEN
IF LENGTH OF SMF30ID IS NOT EQUAL TO SMF30ILN THEN
   DISPLAY 'ERROR. SMF TYPE 30 RECORD MISMATCH.'
   UPON SYSOUT
   DISPLAY 'SMF30ILN = ' SMF30ILN UPON SYSOUT
   DISPLAY 'LENGTH OF SMF30ID = ' LENGTH OF SMF30ID
   UPON SYSOUT
   DISPLAY 'RUN ABORTED.' UPON SYSOUT
   MOVE +16 TO RETURN-CODE
   GOBACK
   END-IF
SUBTRACT BINARY-THREE FROM SMF30IOF GIVING UNSTRING-OFFSET
MOVE LARGEST-INPUT-RECORD (UNSTRING-OFFSET:
   LENGTH OF SMF30ID)
 TO SMF30ID
MOVE SMF30JBN TO STEP-JBN
MOVE SMF30PGM TO STEP-PGM
MOVE SMF30JNM TO STEP-JNM
MOVE SMF30CLS TO STEP-CLS
MOVE SMF30SIT TO STEP-SIT
MOVE SMF30STD TO STEP-STD
MOVE SMF30RST TO STEP-RST
MOVE SMF30RSD TO STEP-RSD
MOVE SMF30UIF TO STEP-UIF
MOVE SMF30GRP TO STEP-GRP
MOVE SMF30RUD TO STEP-RUD
MOVE SMF30STN TO STEP-STN
MOVE SMF30STM TO STEP-STM
MOVE SMF30PGN TO STEP-PGN
MOVE SMF30AST TO STEP-AST
MOVE SMF30PPS TO STEP-PPS
 END-IF.

--
John McKown 
Systems Engineer IV
IT

Administrative Services Group

HealthMarkets(r)

9151 Boulevard 26 * N. Richland Hills * TX 76010
(817) 255-3225 phone * (817)-961-6183 cell
john.mck...@healthmarkets.com * www.HealthMarkets.com

Confidentiality Notice: This e-mail message may contain confidential or 
proprietary information. If you are not the intended recipient, please contact 
the sender by reply e-mail and destroy all copies of the original message. 
HealthMarkets(r) is the brand name for products underwritten and issued by the 
insurance subsidiaries of HealthMarkets, Inc. -The Chesapeake Life Insurance 
Company(r), Mid-West National Life Insurance Company of TennesseeSM and The 
MEGA Life and Health Insurance Company.SM

 

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-19 Thread David Andrews
On Fri, 2010-04-16 at 20:33 -0400, Clark Morris wrote:
> The more interesting question is why use a
> pointer when reference modification works well
> for playing with the SMF30 records?

'splainey?  (That was the first COBOL I'd written in a very long time,
and I was delighted to find pointers at all.  If there's a better way to
handle SMF30 records I'm all ears.)

-- 
David Andrews
A. Duda and Sons, Inc.
david.andr...@duda.com

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-19 Thread Jan MOEYERSONS
On Fri, 16 Apr 2010 11:28:32 -0400, Joe Reichman 
 wrote:

>Are there any rules for doing math on
>Usage is pointer
>

Only one: "Don't do math on a pointer".

Jantje.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-16 Thread Clark Morris
On 16 Apr 2010 08:52:13 -0700, in bit.listserv.ibm-main you wrote:

>On Fri, 2010-04-16 at 11:43 -0400, Walt Farrell wrote:
>> Why would you want to do math on a pointer?
>
>One example: in a COBOL program I wrote awhile ago, I process SMF
>type-30 records.  Those records contain segments whose offsets are
>stored in fullwords - I address those segments by doing pointer
>arithmetic on the address of the SMF30 record.

In response to other postings, TRUNC(OPT) should work as well as
TRUNC(|BIN) without the brain dead code generation if all operands are
either binary or literals.  The more interesting question is why use a
pointer when reference modification works well for playing with the
SMF30 records?  

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-16 Thread Joe Reichman

TRUNC(BIN). Worked than

Sent from my iPhone

On Apr 16, 2010, at 11:47 AM, David Andrews  wrote:


On Fri, 2010-04-16 at 11:28 -0400, Joe Reichman wrote:

I redefined a usage pointer to PIC 9(8) comp to do arithmetic


Have you compiled with TRUNC(BIN)?

--
David Andrews
A. Duda and Sons, Inc.
david.andr...@duda.com

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-16 Thread Chase, John
> -Original Message-
> From: IBM Mainframe Discussion List On Behalf Of Joe Reichman
> 
> I redefined a usage pointer to PIC 9(8) comp to do arithmetic and got
> weird
>   results
> Are there any rules for doing math on
> Usage is pointer

Compiler option TRUNC(BIN) would be "a friend", but specifying COMP-5 on
your REDEFINE would be better.

-jc-

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-16 Thread Patrick Roehl
Make sure you redefine without being signed as 9(9) COMP (or BINARY) and use
the TRUNC(BIN) option.  

Using a signed field or not having TRUNC(BIN) can cause odd results.

-Original Message-
From: IBM Mainframe Discussion List [mailto:ibm-m...@bama.ua.edu] On Behalf
Of Joe Reichman
Sent: Friday, April 16, 2010 11:29 AM
To: IBM-MAIN@bama.ua.edu
Subject: Arithmetic on COBOL usage is pointer

I redefined a usage pointer to PIC 9(8) comp to do arithmetic and got  
weird
  results
Are there any rules for doing math on
Usage is pointer

Sent from my iPhone

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-16 Thread McKown, John
> -Original Message-
> From: IBM Mainframe Discussion List 
> [mailto:ibm-m...@bama.ua.edu] On Behalf Of Joe Reichman
> Sent: Friday, April 16, 2010 10:29 AM
> To: IBM-MAIN@bama.ua.edu
> Subject: Arithmetic on COBOL usage is pointer
> 
> I redefined a usage pointer to PIC 9(8) comp to do arithmetic 
> and got  
> weird
>   results
> Are there any rules for doing math on
> Usage is pointer
> 
> Sent from my iPhone

I use the SET ws-pointer TO ADDRESS OF ... . Something like the following could 
be done:

WORKING-STORAGE SECTION.
77 WS-POINTER POINTER.

...

LINKAGE SECTION.

77 LS-BIG  PIC X OCCURS 1024 TIMES.

...

PROCEDURE DIVISION.

SET WS-POINTER TO ADDRESS OF some-var.
SET ADDRESS OF LS-BIG TO WS-POINTER.
SET ADDRESS OF WS-POINTER TO LS-BIG(5).

The above is equivalent to adding 4 to the current value of WS-POINTER. That's 
because COBOL arrays are 1-origin. 

--
John McKown 
Systems Engineer IV
IT

Administrative Services Group

HealthMarkets(r)

9151 Boulevard 26 * N. Richland Hills * TX 76010
(817) 255-3225 phone * (817)-961-6183 cell
john.mck...@healthmarkets.com * www.HealthMarkets.com

Confidentiality Notice: This e-mail message may contain confidential or 
proprietary information. If you are not the intended recipient, please contact 
the sender by reply e-mail and destroy all copies of the original message. 
HealthMarkets(r) is the brand name for products underwritten and issued by the 
insurance subsidiaries of HealthMarkets, Inc. -The Chesapeake Life Insurance 
Company(r), Mid-West National Life Insurance Company of TennesseeSM and The 
MEGA Life and Health Insurance Company.SM

 

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-16 Thread Farley, Peter x23353
> -Original Message-
> From: IBM Mainframe Discussion List [mailto:ibm-m...@bama.ua.edu] On
> Behalf Of Joe Reichman
> Sent: Friday, April 16, 2010 11:29 AM
> To: IBM-MAIN@bama.ua.edu
> Subject: Arithmetic on COBOL usage is pointer
> 
> I redefined a usage pointer to PIC 9(8) comp to do arithmetic and got
> weird results.  Are there any rules for doing math on Usage is pointer

What kind of "weird" results?  I have done this before, but I redefined
using PIC S9(09) BINARY rather than 9(8) COMP.  Are you using the
TRUNC(BIN) compiler option?  Check the manual for impact of the TRUNC
option for more info.

Sometimes it helps to use the LIST compiler option to see exactly what
the compiler is generating for your pointer arithmetic statements,
sometimes you can determine your problem more easily that way.

HTH

Peter

 
This message and any attachments are intended only for the use of the addressee 
and
may contain information that is privileged and confidential. If the reader of 
the 
message is not the intended recipient or an authorized representative of the
intended recipient, you are hereby notified that any dissemination of this
communication is strictly prohibited. If you have received this communication in
error, please notify us immediately by e-mail and delete the message and any
attachments from your system.


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-16 Thread David Andrews
On Fri, 2010-04-16 at 11:43 -0400, Walt Farrell wrote:
> Why would you want to do math on a pointer?

One example: in a COBOL program I wrote awhile ago, I process SMF
type-30 records.  Those records contain segments whose offsets are
stored in fullwords - I address those segments by doing pointer
arithmetic on the address of the SMF30 record.

-- 
David Andrews
A. Duda and Sons, Inc.
david.andr...@duda.com

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-16 Thread David Andrews
On Fri, 2010-04-16 at 11:28 -0400, Joe Reichman wrote:
> I redefined a usage pointer to PIC 9(8) comp to do arithmetic

Have you compiled with TRUNC(BIN)?

-- 
David Andrews
A. Duda and Sons, Inc.
david.andr...@duda.com

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: Arithmetic on COBOL usage is pointer

2010-04-16 Thread Walt Farrell
On Fri, 16 Apr 2010 11:28:32 -0400, Joe Reichman 
wrote:

>I redefined a usage pointer to PIC 9(8) comp to do arithmetic and got
>weird
>  results
>Are there any rules for doing math on
>Usage is pointer
>

Why would you want to do math on a pointer?

-- 
Walt

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Arithmetic on COBOL usage is pointer

2010-04-16 Thread Joe Reichman
I redefined a usage pointer to PIC 9(8) comp to do arithmetic and got  
weird

 results
Are there any rules for doing math on
Usage is pointer

Sent from my iPhone

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html