HP3000-L Archives

May 2010, 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:
Reply To:
Date:
Wed, 26 May 2010 12:03:16 -0500
Content-Type:
text/plain
Parts/Attachments:
text/plain (148 lines)
A quick and dirty method would be to check the HP variable HPQUIET if it 
is FALSE odds are that you are not in block mode, if TRUE you might be 
in block mode.
Explanation: V/Plus places the session in QUIET mode, so if you find 
this variable to be FALSE then you can be almost sure that you are not 
in block mode, likewise and aborted block mode process could have taken 
you out of block mode, but QUIET mode is still TRUE.

A more reliable somewhat "Hardcoded" method would be to call PROCINFO 
intrinsic to retrieve the calling program file name. Then in you 
subroutine check the name, or maintain an external table of program 
names and their block mode status.

Calling procinfo from Cobol:

After compiling and linking the source below, add the following code 
into you cobol subroutine.

01 PROGRAMNAME PIC X(36).

CALL "PROCNAME" USING PROGRAMNAME.
*****************************************************************

$CONTROL RLFILE,LIST,DYNAMIC,BOUNDS,POST85
 IDENTIFICATION DIVISION.
 PROGRAM-ID.  PROCNAME.
 AUTHOR.  MICHAEL ANDERSON.
 DATE-COMPILED.
 ENVIRONMENT DIVISION.
 CONFIGURATION SECTION.
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 01  PROGNAME-ERROR1                PIC S9(04) COMP VALUE ZERO.
 01  PROGNAME-ERROR2                PIC S9(04) COMP VALUE ZERO.
 01  PROGNAME-PIN-NO                PIC S9(04) COMP VALUE ZERO.
 01  PROGNAME-ITEMNO1               PIC S9(04) COMP VALUE ZERO.
 01  P-PIN-NO                       PIC  9(04)      VALUE ZERO.
 01  PROGNAME-ITEM1-AREA.
     05  PROGNAME-ITEM1            PIC XX VALUE SPACES.
     05  FILLER REDEFINES PROGNAME-ITEM1.
         10  PROGNAME-PIN          PIC S9(4) COMP.
 01  PROGNAME-ITEMNO2               PIC S9(04) COMP VALUE ZERO.
 01  PROGNAME-ITEM2                 PIC X(30) VALUE SPACES.
*
*
******************************************************************
 LINKAGE SECTION.

 01  THE-PROGRAM-NAME       PIC X(36).
*
/
******************************************************************
 PROCEDURE DIVISION USING THE-PROGRAM-NAME.

******************************************************************
*
 HSKPG-100.
     MOVE ZERO TO PROGNAME-PIN-NO,
                  PROGNAME-ERROR1,
                  PROGNAME-ERROR2.
     MOVE SPACES TO PROGNAME-ITEM1.
     MOVE 1 TO PROGNAME-ITEMNO1.
 GET-PROC-PIN-200.
     CALL INTRINSIC "PROCINFO" USING PROGNAME-ERROR1,
                                     PROGNAME-ERROR2,
                                     PROGNAME-PIN-NO,
                                     PROGNAME-ITEMNO1,
                                     PROGNAME-ITEM1.
     IF PROGNAME-ERROR1 IS NOT EQUAL TO ZERO
     OR PROGNAME-ERROR2 IS NOT EQUAL TO ZERO
        GO TO ABNORMAL-EOJ-9999.
 GET-PROC-NAME-300.
     MOVE 10 TO PROGNAME-ITEMNO2.
     MOVE PROGNAME-PIN TO P-PIN-NO.
     MOVE P-PIN-NO TO PROGNAME-PIN-NO.
     MOVE SPACES TO PROGNAME-ITEM2.
     CALL INTRINSIC "PROCINFO" USING PROGNAME-ERROR1,
                                     PROGNAME-ERROR2,
                                     PROGNAME-PIN-NO,
                                     PROGNAME-ITEMNO2,
                                     PROGNAME-ITEM2.
     IF PROGNAME-ERROR1 IS NOT EQUAL TO ZERO
     OR PROGNAME-ERROR2 IS NOT EQUAL TO ZERO
        GO TO ABNORMAL-EOJ-9999.
 NORMAL-EOJ-9999.
     MOVE   PROGNAME-ITEM2 TO THE-PROGRAM-NAME.
       GOBACK.
 ABNORMAL-EOJ-9999.
     DISPLAY "ERROR ENCOUNTERED CALLING ""PROCINFO"" INTRINSIC"
       GOBACK.
 END PROGRAM PROCNAME.





Roy Brown wrote:
> In message <[log in to unmask]>, Michael 
> Caplin <[log in to unmask]> writing at 11:20:01 in his/her local time 
> opines:-
>
>> I have a subprogram that can be called from a block or character mode 
>> main
>> program and I want the sub to know which called it without anything 
>> being
>> passed in linkage.  I can think of some ugly ways to do it.  Does 
>> anyone know
>> of an easy/simple way.
>> TIA,
>> mike
>
> If I'm not being too pedantic, there's no such thing as a 'block mode 
> or character mode' program, but rather a program that has its 
> terminal, or some equivalent I/O device, in block or character mode at 
> the time the subprogram is called.
>
> Looked at like this, it's perhaps clearer that what the subprogram 
> needs to do when it starts up is to query the terminal to see what 
> mode it is in at that time.
>
> If you know this will always be used with Reflection, you can query 
> that:-
> ===================================================
> Syntax
> object.BlockMode
> object.BlockMode = Value
>
> Works with
> Data type       Boolean
>
> Description
>
> Returns (first syntax line) or specifies (second syntax line) whether 
> Reflection is in HP block mode. Typically this property is set by the 
> host rather than by the user.
>
> Values
>
> The default value is False.
> ===================================================
>
> There's probably something you can do based on an escape sequence 
> which will work with any emulator or even a real HP terminal, though I 
> haven't seen one of those lately.

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

ATOM RSS1 RSS2