HP3000-L Archives

February 2005, Week 2

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:
Günter Kuhn <[log in to unmask]>
Reply To:
Günter Kuhn <[log in to unmask]>
Date:
Mon, 14 Feb 2005 14:40:26 +0000
Content-Type:
text/plain
Parts/Attachments:
text/plain (247 lines)
Hello all,

another way for doing BIT operations are the COBOLII/X Enhancements:

HP_BYTE_PACK and HP_BYTE_UNPACK



Robert Mills schrieb:
> Bob,
>
> You could replace your SUB-GET-TERMOPTIONS and SUB-PUT-TERMOPTIONS performs with calls to BITMAPCNV. Does exactly the same thing but it also returns a status indicating if the conversion was successful.
>
> BITMAPCNV is documented in Appendix I of the VPLUS Reference Manual.
>
> regards,
>
> Robert W.Mills
> Systems Development Manager
> Windsong Services
> (020) 8309 3604
>
>
> HP-3000 Systems Discussion wrote:
>
>>After detecting that function key has been pressed, you can force a
>>read of the screen as if they had pressed enter and proceed.
>>...
>>111900 01  BITMAP-FIELDS.
>>111950*
>>112000*** A TWO WORD BITMAP IS USED SO THAT A TRUE LOGICAL
>>112050*** INTERPRETATION OF ALL 16 BITS OF THE WORD CAN BE
>>112100*** DETERMINED, OTHER WISE BIT ZERO BEING ON COULD
>>112150*** CAUSE PROBLEMS IN THE CONVERSION ROUTINES (NEGATIVE)
>>112200*
>>112250     05 BITMAP.
>>112300        10 BM-DOUBLE        PIC S9(9) COMP.
>>112350        10 BM-SPLIT REDEFINES BM-DOUBLE.
>>112400            15 BM-IGNORE    PIC S9(4) COMP.
>>112450            15 BM-WORD      PIC XX.
>>112500     05 BYTEMAP.
>>112550        10 BM-BYTE OCCURS 16 TIMES INDEXED BY BMX PIC 9.
>>112600           88 BIT-OFF       VALUE 0.
>>112650           88 BIT-ON        VALUE 1.
>>112700
>>...
>>115150 01 TERMOPTIONS-BYTEMAP.
>>115200    05 TERMOPTIONS-RESERVED PIC X(9).
>>115250    05 TERMOPTIONS-9-10     PIC 99.
>>115300       88 DISABLE-TIMEOUT   VALUE 00, 11.
>>115350       88 ENABLE-TIMEOUT    VALUE 01.
>>115400    05 TERMOPTIONS-11-12    PIC 99.
>>115450       88 NORMAL-CLOSE      VALUE 00.
>>115500       88 DONT-CLEAR-CLOSE  VALUE 10.
>>115550    05 TERMOPTIONS-13-14    PIC 99.
>>115600       88 NORMAL-READ       VALUE 00, 11.
>>115650       88 AUTO-READ         VALUE 01.
>>115700    05 TERMOPTIONS-15       PIC 9.
>>115750       88 ENABLE-BELL       VALUE 0.
>>115800       88 DISABLE-BELL      VALUE 1.
>>...
>>
>>676900 Z-900-DO-AUTOREAD.
>>676950*****
>>677000***** Read form WITHOUT user having pressed enter
>>677050*****
>>677100     SET VREAD-NOT-OK TO TRUE
>>677150     SET VPLUS-OK TO TRUE
>>677200     PERFORM SUB-GET-TERMOPTIONS
>>677250     SET AUTO-READ TO TRUE
>>677300     PERFORM SUB-PUT-TERMOPTIONS
>>677350     CALL INTRINSIC "VREADFIELDS" USING COMAREA.
>>677400     IF VPLUS-OK
>>677450        PERFORM SUB-GET-TERMOPTIONS
>>677500        SET NORMAL-READ TO TRUE
>>677550        PERFORM SUB-PUT-TERMOPTIONS
>>677600        PERFORM Z-900-PROCESS-ENTER-KEY
>>677650     ELSE
>>677700      SET ABORT TO TRUE
>>677750      MOVE
>>677800       "**** Paragraph: Z-900-AUTOREAD - Terminal Read"
>>677850         TO ERROR-LOCATION
>>677900      PERFORM Z-100-GET-ERROR-MESSAGE.
>>...
>>682950 SUB-GET-TERMOPTIONS.
>>683000     MOVE TERMOPTIONS-WORD TO BM-WORD
>>683050     PERFORM SUB-BIT-TO-BYTE
>>683100     MOVE BYTEMAP TO TERMOPTIONS-BYTEMAP.
>>683150
>>683200 SUB-PUT-TERMOPTIONS.
>>683250     MOVE TERMOPTIONS-BYTEMAP TO BYTEMAP
>>683300     PERFORM SUB-BYTE-TO-BIT
>>683350     MOVE BM-WORD TO TERMOPTIONS-WORD.
>>...
>>83950 SUB-BIT-TO-BYTE.
>>684000     MOVE ALL ZEROS TO BYTEMAP.
>>684050     PERFORM VARYING BMX FROM 16 BY -1 UNTIL BMX < 1
>>684100         DIVIDE BM-DOUBLE BY 2 GIVING BM-DOUBLE
>>684150                            REMAINDER BM-BYTE(BMX)
>>684200     END-PERFORM.
>>684250
>>684300 SUB-BYTE-TO-BIT.
>>684350     MOVE ZERO TO BM-DOUBLE
>>684400     PERFORM VARYING BMX FROM 1 BY 1 UNTIL BMX > 16
>>684450         MULTIPLY 2 BY BM-DOUBLE
>>684500         ADD BM-BYTE(BMX) TO BM-DOUBLE
>>684550     END-PERFORM.
>>
>>There may be better ways to handle the bit/byte conversions now, but
>>it works.
>>
>>Bob Comeau
>>Sr. Systems Programmer Analyst
>>Crossley Carpet Mills Ltd.
>>(902)895-5491 ex 139
>>
>>
>>-----Original Message-----
>>From: HP-3000 Systems Discussion [mailto:[log in to unmask]]On
>>Behalf Of Matthew Perdue
>>Sent: February 11, 2005 6:54 PM
>>To: [log in to unmask]
>>Subject: Re: VPLUS and VSETERROR/VREADFIELDS/VFIELDEDITS
>>
>>
>>Quoting Peter Smithson <[log in to unmask]>:
>>
>>
>>>In article <[log in to unmask]>,
>>>[log in to unmask] says...
>>>
>>>
>>>>The screen buffer is not read if a function key is pressed, only if
>>>>enter is pressed. If the user pressed a function key, and you want
>>>>to know the contents of the screen buffer, you have to force a read
>>>>with VGETBUFFER.
>>>
>>>Thanks for the replies - I know there isn't much point in running the
>>>VFIELDEDITS when no buffer is present (as they hit a function key).
>>>
>>>I'm trying to figure out how some customers code is working.  In the
>>>code sample I gave, you can see that there is no conditinal
>>>execution of code.  I think they do this is it's a generic library
>>>of calls but I wrote a simple example program showing the behaviour.
>>>
>>>Without the VSETERROR and without setting numerrs, I get an error
>>>from VREADFIELDS (due to the required fields) whether I hit a
>>>function key or enter.
>>>
>>>With the VSETERROR and setting numerrs, I only get an error from
>>>VREADFIELDS if enter is pressed.
>>>
>>>Anyone know why?
>>>
>>>Cheers
>>>
>>>Peter
>>
>>This is a code snippet of what I use:
>>
>> MOVE SPACES        TO MBR-MSTR-SPACES.
>> MOVE HOLD-MEMB-ID  TO S-MM-MBR-KEY.
>> MOVE "MEMBER_MAST" TO COM-NFNAME.
>>
>> CALL "VGETNEXTFORM" USING COMAREA.
>> IF COM-STATUS NOT = 0
>>    MOVE 0 TO COM-STATUS
>>    CALL "VCLOSETERM" USING COMAREA
>>...etc....
>>
>> CALL "VPUTBUFFER" USING COMAREA MBR-MSTR-SCREEN
>>                                 MBR-MSTR-BUFFER.
>> MOVE SPACES TO ERR-MSG.
>> MOVE "Enter member number, press enter"   TO ERR-MSG.
>> MOVE 2 TO FIELD-NUM.
>> CALL "VSETERROR" USING COMAREA FIELD-NUM ERR-MSG MSG-LEN.
>> CALL "VSHOWFORM" USING COMAREA.
>>*
>>110-PROCESS-MBR-MSTR-SCREEN.
>>
>> MOVE 0 TO COM-STATUS COM-NUMERRS.
>> CALL "VREADFIELDS" USING COMAREA.
>>
>> IF ENTER-TIME-OUT GO TO 010-SETUP-MAIN-SCREEN.
>>
>> CALL "VGETBUFFER"  USING COMAREA MBR-MSTR-SCREEN
>> IF ENTER-KEY GO TO 120-PROCESS-FIELD-EDITS.
>> IF           F1 GO TO  010-SETUP-MAIN-SCREEN
>>      ELSE IF F2 GO TO 100A-MEMBER-ADDRESS
>>      ELSE IF F3 GO TO 100F-MEMBER-FINANCIAL
>>      ELSE IF F4 GO TO 100I-MEMBER-INQUIRIES
>>      ELSE IF F5 MOVE SPACES TO HOLD-MEMB-ID
>>                 GO TO  100-MEMBER-MASTER
>>      ELSE IF F6 GO TO
>>      ELSE IF F7 GO TO
>>      ELSE IF F8 GO TO  010-SETUP-MAIN-SCREEN
>>      ELSE
>>        MOVE SPACES TO ERR-MSG
>>        MOVE "INVALID KEY SELECTED"  TO ERR-MSG
>>        CALL "VPUTWINDOW" USING COMAREA ERR-MSG MSG-LEN
>>        CALL "VSHOWFORM"  USING COMAREA
>>        GO TO 110-PROCESS-MBR-MSTR-SCREEN.
>>*
>>120-PROCESS-FIELD-EDITS.
>>
>> CALL "VFIELDEDITS" USING COMAREA.
>> IF COM-NUMERRS NOT = 0
>>    MOVE SPACES TO ERR-MSG
>>    CALL "VERRMSG"    USING COMAREA ERR-MSG MSG-LEN R-LEN
>>    CALL "VPUTWINDOW" USING COMAREA ERR-MSG MSG-LEN
>>    CALL "VSHOWFORM"  USING COMAREA
>>    GO TO 110-PROCESS-MBR-MSTR-SCREEN.
>>*
>>130-PROCESS-DATA.
>>
>> CALL "VGETBUFFER" USING COMAREA MBR-MSTR-SCREEN
>>                                 MBR-MSTR-BUFFER.
>>
>>...etc....
>>
>>* 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 *
>

--
Mit freundlichen Grüßen / Best regards

Günter Kuhn

SSD IT Consulting GmbH
CH 6404 Greppen
Switzerland

EMail: [log in to unmask]
WWW:   www.ssd-it.ch
Skype: gkuhndo

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

ATOM RSS1 RSS2