HP3000-L Archives

October 2002, Week 4

HP3000-L@RAVEN.UTC.EDU

Options: Use Monospaced Font
Show Text Part by Default
Show All Mail Headers

Message: [<< First] [< Prev] [Next >] [Last >>]
Topic: [<< First] [< Prev] [Next >] [Last >>]
Author: [<< First] [< Prev] [Next >] [Last >>]

Print Reply
Subject:
From:
Michael Anderson <[log in to unmask]>
Reply To:
Michael Anderson <[log in to unmask]>
Date:
Thu, 24 Oct 2002 16:15:23 -0500
Content-Type:
text/plain
Parts/Attachments:
text/plain (286 lines)
Simplicity is the best, most of the time. However, when I think about
reading numeric data from a character string I like to consider the
possibilities. For Example: A user may enter numbers like 9,562.23, or
-5,562,295.9567 in both cases a simple VPLUS edit will fail, and for
different reasons. In some cases you'll run into run-time COBOL problems
like Illegal ASCII Digits. You want your app to be simple to use, not
confusing. Users should be able to enter numbers left, center, or right
justified, with or without commas, and/or decimal points. Anyway, this
is what I use to read numeric data from a character string. I call a
little home-grown subroutine "NUMGET", and it handles all this nonsense
for me. Below, is a fairly basic version of it. You can add more stuff
to it, like dollar sign support, and so on. I have another version
somewhere that returns the numeric string as packed decimal, with four
decimal places, and another that returns 64 bit HP-REAL, and IEEE-REAL.
I keep this in a XL, to make sure all numeric strings are processed
exactly the same. Applications written using VPLUS Numeric edits are
usually very inconsistent in the way numeric input is processed, because
each field has it's own code, and each programmer codes it differently.
This doesn't just apply to reading numeric input from a screen, it
doesn't matter if it is a field on a screen, or a field in a record of a
file.



Example:
$CONTROL USLINIT, POST85, LINES=59
 IDENTIFICATION DIVISION.
 PROGRAM-ID.     STU001R.
 AUTHOR.     MICHAEL ANDERSON.
 ENVIRONMENT DIVISION.
 CONFIGURATION SECTION.
 SOURCE-COMPUTER.  HP-3000.
 OBJECT-COMPUTER.  HP-3000.
 DATA DIVISION.
 WORKING-STORAGE SECTION.

 01 NUM9999      PIC 9(8) VALUE 0.
 01 NUM99-99     PIC 9(4)V9(4) VALUE ZERO.
 01 DECIMAL-VAL PIC S9(4) COMP VALUE 0.
 01 NUMZZZZ      PIC Z,ZZ9.9999 VALUE ZERO.
 01 DEC-PLACES   PIC Z9 VALUE ZERO.


 01 NUM1         PIC X(14) VALUE SPACES.
 01 NUM2         PIC 9(14) VALUE ZERO.
 01 NUMDEC       PIC S9(4) COMP VALUE 0.
 01 NUMERR       PIC S9(4) COMP VALUE 0.

 PROCEDURE DIVISION.
 BEGIN-0000.

     MOVE "   5,091.92285" TO NUM1.
     INITIALIZE NUM2 NUMDEC NUMERR.
     CALL "NUMGET" USING NUM1 NUM2 NUMDEC NUMERR.
     COMPUTE NUM99-99 = NUM2 / ( 10 ** NUMDEC ).
*
*  DISPLAY RESULTS
     MOVE NUMDEC TO DEC-PLACES.
     MOVE NUM99-99 TO NUMZZZZ.
     DISPLAY "NUM1 [" NUM1 "]".
     DISPLAY "Decimal Places: " DEC-PLACES.
     DISPLAY "NUM99-99 [" NUM99-99 "]".
     DISPLAY "NUMZZZZ [" NUMZZZZ "]".
     STOP RUN.




$PAGE "THIS PROGRAM ---> NUMGET   "

*
*     |           |           |           |           |
*     |           |           |           |           |
*>>>>\|/<<<< >>>>\|/<<<< >>>>\|/<<<< >>>>\|/<<<< >>>>\|/<<<<
* >>>\|/<<<   >>>\|/<<<   >>>\|/<<<   >>>\|/<<<   >>>\|/<<<
*  >>\|/<<     >>\|/<<     >>\|/<<     >>\|/<<     >>\|/<<
*   >\|/<       >\|/<       >\|/<       >\|/<       >\|/<
*    \|/         \|/         \|/         \|/         \|/
*     Y           Y           Y           Y           Y
*
$TITLE "NUMGET - SUBROUTINE TO GET NUMBER FROM IMAGE BUFFER"
$CONTROL RLFILE,LIST,DYNAMIC,BOUNDS
 IDENTIFICATION DIVISION.
 PROGRAM-ID. NUMGET.
 AUTHOR.     JOE W CHAMRAD.
 DATE-COMPILED.

**************************************************************
*                                                            *
*  THIS SUBROUTINE CONVERTS THE NUMBERS AS ENTERED AT THE    *
*  TERMINAL INTO NUMERIC, SIGNED NUMBERS THAT CAN BE USED    *
*  IN THE PROGRAM.                                           *
*                                                            *
*  PARAMETERS:                                               *
*                                                            *
*  NUM-1     A 14 CHARACTER FIELD CONTAINING THE NUMBER AS   *
*            THE OPERATOR TYPED IT.                          *
*                                                            *
*  NUM-2     THE 14 ASCII DIGIT SIGNED NUMERIC VALUE OF NUM-1*
*            THAT IS RETURNED.                               *
*                                                            *
*  N-DEC     AN INTEGER WHICH RETURNS THE NUMBER OF DECIMAL  *
*            PLACES FOUND IN THE NUMBER.                     *
*                                                            *
*  N-ERR     AN INTEGER WHICH RETURNS A 1 IF NUM-1 DID NOT   *
*            CONTAIN VALID NUMERIC INFORMATION OR RETURNS 0  *
*            IF A GOOD NUMBER WAS FOUND.                     *
*                                                            *
**************************************************************

 ENVIRONMENT DIVISION.

 CONFIGURATION SECTION.
 SOURCE-COMPUTER. HP3000.
 OBJECT-COMPUTER. HP3000.
$PAGE
 DATA DIVISION.
 WORKING-STORAGE SECTION.

 01  N                     PIC 9(4) COMP.
 01  N1                    PIC 9(4) COMP.
 01  N2                    PIC 9(4) COMP.
 01  DECIMAL-SW            PIC X.
 01  COMMA-SW              PIC X.
 01  MINUS-SW              PIC X.

 LINKAGE SECTION.

 01  NUM-1.
     02  X1                PIC X  OCCURS 14 TIMES.

 01  NUM-2.
     02  X2                PIC X  OCCURS 14 TIMES.
 01  FILLER REDEFINES NUM-2.
     02  NUM-2N            PIC S9(14).

 01  N-DEC                 PIC 9(4) COMP.
 01  N-ERR                 PIC 9(4) COMP.
$PAGE
 PROCEDURE DIVISION USING NUM-1 NUM-2 N-DEC N-ERR.

 START-HERE.
     MOVE SPACES TO NUM-2.
     MOVE ZERO TO N-DEC N-ERR.
     MOVE 14 TO N.

 1ST-LOOP.
     IF N NOT = ZERO
         IF X1 (N) = SPACE
             SUBTRACT 1 FROM N
             GO TO 1ST-LOOP.
     COMPUTE N1 = N + 1.
     MOVE 14 TO N2.
     MOVE "0" TO DECIMAL-SW COMMA-SW MINUS-SW.

 2ND-LOOP.
     SUBTRACT 1 FROM N1.
     IF N1 = ZERO GO TO FINISH-UP.
     IF X1 (N1) = SPACE GO TO 2ND-LOOP.
     IF X1 (N1) = "-"
         IF MINUS-SW = "1"
             MOVE "1" TO N-ERR
             GO TO 2ND-LOOP
         ELSE
             MOVE "1" TO MINUS-SW
             GO TO 2ND-LOOP.
     IF X1 (N1) = ","
         MOVE "1" TO COMMA-SW
         GO TO 2ND-LOOP.
     IF X1 (N1) = "."
         IF DECIMAL-SW = "1" OR COMMA-SW = "1"
             MOVE 1 TO N-ERR
             GO TO 2ND-LOOP
         ELSE
             MOVE "1" TO DECIMAL-SW
             GO TO 2ND-LOOP.
     IF X1 (N1) LESS THAN "0" OR GREATER THAN "9"
         MOVE 1 TO N-ERR
         GO TO 2ND-LOOP.
     MOVE X1 (N1) TO X2 (N2).
     IF DECIMAL-SW NOT = "1" ADD 1 TO N-DEC.
     SUBTRACT 1 FROM N2.
     GO TO 2ND-LOOP.

 FINISH-UP.
     INSPECT NUM-2 REPLACING LEADING SPACES BY "0".
     IF MINUS-SW = "1" COMPUTE NUM-2N = - NUM-2N.
     IF DECIMAL-SW = "0" MOVE ZERO TO N-DEC.
     IF N-ERR NOT = ZERO MOVE ZERO TO NUM-2N N-DEC.

 ALL-DONE.
     EXIT PROGRAM.
 END PROGRAM NUMGET.


--
Michael Anderson
Spring Independent School District
16717 Ella Boulevard
Houston, Texas 77090-4299
office: 281.586.1105
fax: 281.586.1187
-

>>> "Rao, Raghu" <[log in to unmask]> 10/24/02 02:03PM >>>
Thanks,

The ARB stuff is not only way too much of a hammer, but also a heavy
hammer
and I have very short in which I cannot lift him, leave alone the
killer
blow...

The definition of user entry screen field to X(09) followed by JUSTIFY
RIGHT
and FILL LEADING "0" worked...

Thanks a lot..

Raghu..

-----Original Message-----
From: [log in to unmask]
[mailto:[log in to unmask]]
Sent: Thursday, October 24, 2002 2:20 PM
To: [log in to unmask]; [log in to unmask]
Subject: RE: VPLUS: ARBTOSCREEN or SCREENTOARB


OOps..Mea Culpa!

Make that RIGHT JUSTIFY  ;).


How about just setting the forms file to RIGHT justify and zero fill on
the
FINAL for this field, then use normal COBOL "MOVE <X(9) screen-field>
TO
<working Storage PIC S9(9) COMP>.

This ARB stuff seems like way too much of a hammer.

Rich



Rich Trapp <mailto:[log in to unmask]>

Consulting for Agilent Technologies, Loveland, Colorado.

Managed Business Solutions <http://www.thinkmbs.com/>
200 South College Avenue
Fort Collins, Colorado 80524-2811
970.679.2221 (voice)
970.669.3071 (fax)



-----Original Message-----
From: Rao, Raghu [mailto:[log in to unmask]]
Sent: Thursday, October 24, 2002 11:46 AM
To: [log in to unmask]
Subject: VPLUS: ARBTOSCREEN or SCREENTOARB


Hi,

Can anyone give any examples for usage of ARBTOSCREEN or SCREENTOARB
commands under FORMSPEC in VPlus ?

I am in need of converting data entered by users online {could be 9(09)
or
X(09)} into 9(09) COMP as DINIT.

Thanks
Raghu

* To join/leave the list, search archives, change list settings, *
* etc., please visit http://raven.utc.edu/archives/hp3000-l.html *

* To join/leave the list, search archives, change list settings, *
* etc., please visit http://raven.utc.edu/archives/hp3000-l.html *

* To join/leave the list, search archives, change list settings, *
* etc., please visit http://raven.utc.edu/archives/hp3000-l.html *

ATOM RSS1 RSS2