[Search for users] [Overall Top Noters] [List of all Conferences] [Download this site]

Conference turris::tpu_notes

Title:DECTPU and EVE Notes Conference
Notice:Use UHUH:: to access kits: see note 1735
Moderator:HNDYMN::MCCARTHY
Created:Mon Feb 03 1986
Last Modified:Tue May 27 1997
Last Successful Update:Fri Jun 06 1997
Number of topics:1947
Total number of notes:9831

1944.0. "Post-TPU behavior in BASIC program" by CSC32::HENNING (A rose with no thorns) Fri Apr 04 1997 17:43

    Hi all,
    
    Am not sure that this is a problem with TPU handler cleanup, LIB$REVERT 
    or BASIC.  All suggestions on the following are welcome!
    
    A BASIC program uses the full TPU interface to create an output file. 
    On exit from EVE, the program calls TPU$CLEANUP and LIB$REVERT to
    delete the TPU context and revert to delete the TPU$HANDLER.  Within a
    FOR loop that contains a WHEN ERROR block (user-written attached error 
    handler), it reads the output file's records.  
    
    When the file's EOF is reached, the INPUT statement should fail with
    ERR=11 (end of file) and the WHEN ERROR block's handler should kick in:
    
      (expected behavior)
      This is the text from the input file.
      You should be seeing this text in the editor.
    
    
      eof trapped
      done
    
    Instead, the BASIC default condition handler kicks in:
    
      (observed behavior)
    
      This is the text from the input file.
      You should be seeing this text in the editor.
      %BAS-F-ENDFILDEV, End of file on device
      -BAS-I-ON_CHAFIL, on channel 2 for file
      DKA300:[HENNING.TEST]TPU_OUTPUT_FILE.TX0
      -RMS-E-EOF, end of file detected
      %TRACE-F-TRACEBACK, symbolic stack dump follows
      module name     routine name             line       rel PC     abs PC
    
                                                        000A63EE    000A63EE
                                                        000A3DE4    000A3DE4
                                                        000A2C0A    000A2C0A
                                                        0009E1A3    0009E1A3
      CALLABLE_TPU    CALLABLE_TPU             130      0000022C    0000122C
    
    A similar program that reads the output file but doesn't call TPU$*
    routines executes correctly:
    
      This is the text from the input file.
      You should be seeing this text in the editor.
    
    
      eof trapped
      done
    
    Is this expected behavior for DECTPU V3.1 (OpenVMS VAX V6.1) in a
    program compiled with BASIC V3.8?
    
    I've attached 2 programs that show the behaviors. 
    
    
    Thanks in advance,
    Mary
    
    
    $ create callable_tpu.bas
1	PROGRAM callable_tpu

    OPTION TYPE = EXPLICIT
    EXTERNAL LONG CONSTANT tpu$_success,         &
                           tpu$_quitting,        &
                           tpu$_exiting,         &
                           tpu$m_delete_context

    EXTERNAL LONG FUNCTION tpu$initialize,       &
                           tpu$handler,          &
                           tpu$execute_inifile,  &
                           tpu$control,          &
                           tpu$cleanup,          &
                           lib$match_cond,       &
                           tpu_startup

    EXTERNAL SUB           lib$establish,        &
                           lib$revert,           &
                           lib$stop,             &
                           create_files

    DECLARE LONG           bpv(1% TO 2%),        &
                           stat,                 &
			   i%,			 &
                           condition_value

    DECLARE STRING         out_text

    DECLARE STRING 	   rec_string

    MAP (open_files) LONG channel_array(1% TO 119%)

    CALL create_files

    CALL lib$establish (loc(tpu$handler) BY VALUE)

    bpv(1%) = LOC(tpu_startup)
    bpv(2%) = 0%

    stat = tpu$initialize (bpv(1%))
    IF stat <> tpu$_success THEN
        PRINT "Error calling TPU$INITIALIZE"
        CALL lib$stop (stat BY VALUE)
    END IF

    stat = tpu$execute_inifile ()
    IF stat <> tpu$_success THEN
        PRINT "Error calling TPU$EXECUTE_INIFILE"
        CALL lib$stop (stat BY VALUE)
    END IF

    stat = tpu$control ()

    condition_value = lib$match_cond (stat,         &
                                      tpu$_exiting, &
                                      tpu$_quitting )
    SELECT condition_value
        CASE = 1%
            out_text = "Since you EXITed the editor, an output " + &
                       "file (TPU_OUTPUT_FILE.TXT) was created."
        CASE = 2%
            out_text = "Since you QUIT out of the editor, no output " + &
                       "file was created."
        CASE ELSE
            PRINT "Error calling TPU$CONTROL"
            CALL lib$stop (condition_value BY VALUE)
    END SELECT

    clean_up:
        stat = tpu$cleanup (tpu$m_delete_context)
        IF stat <> tpu$_success THEN
            PRINT "Error calling TPU$CLEANUP"
            CALL lib$stop (stat BY VALUE)
        END IF

    CALL lib$revert()

    PRINT out_text

    ! after call to LIB$REVERT, would expect the user-written handler
    ! associated with WHEN ERROR to kick in.  Instead, the default
    ! handler kicks in.
    
    OPEN "TPU_OUTPUT_FILE.TXT" FOR INPUT AS FILE 2%, RECORDSIZE 70%

	FOR i% = 0% STEP 1% WHILE -1%
		WHEN ERROR IN
			INPUT #2%, rec_string
		USE
			EXIT HANDLER	IF ERR <> 11%
			print
			print
			print "eof trapped"
			continue 10000
		END WHEN
		print rec_string
	NEXT i%
	print
	print
	print 'eof NOT trapped'
	goto 10000

 10000	print 'done'
	
 	END PROGRAM

12000	SUB create_files
    !
    ! This subprogram will create a very simple TPU command file and a
    ! short input file.  Like the DCL interface to TPU, the callable
    ! interface to TPU allows one to invoke a TPU 'command' file.  It also
    ! allows one to specify the name of the file to be edited.
    !
    ! Please note that this subprogram is used only to create files which
    ! help demonstrate the full callable interface to TPU.  You can use
    ! your own file names and file contents.
    !
    OPTION TYPE = EXPLICIT

    !
    ! Create a simple command file.  The command file is not required.
    ! However, this program demonstrates how it can be used.  The command
    ! file can contain any 'legal' TPU commands or procedures which you
    ! would like to be executed when the editor is invoked.  This command
    ! file uses a fairly simple TPU command to change the status line of
    ! the editor.  To be obvious, the text of the status line is changed
    ! and the status line is caused to blink.  While this is somewhat
    ! irritating and probably undesirable in normal editing situations, it
    ! is done here to prove that the command file is invoked.
    !
    OPEN "tpu_command_file.tpu" FOR OUTPUT AS FILE #1, RECORDSIZE 132%
    PRINT #1, 'set (status_line, get_info(window, "current"), blink, ' + &
              '"This was caused by the command file!")'
    CLOSE #1
    PRINT "Command file 'TPU_COMMAND_FILE.TPU' created."

    !
    ! Create a sample input file.  This will be the file that
    ! is edited.
    !
    OPEN "tpu_input_file.txt" FOR OUTPUT AS FILE #2
    PRINT #2, "This is the text from the input file."
    PRINT #2, "You should be seeing this text in the editor."
    CLOSE #2
    PRINT "Input file 'TPU_INPUT_FILE.TXT' created."
    SLEEP 3%
END SUB

14000	FUNCTION LONG tpu_startup
    !
    ! This function is called by TPU$INITIALIZE.  An item list will be
    ! built that contains initialization parameters. The address of the
    ! item list is passed to VAXTPU.  The item list is loaded with
    ! information about the input file, section file, file I/O routine,
    ! options, etc.
    !
    OPTION TYPE = EXPLICIT

    EXTERNAL LONG FUNCTION fileio_routine

    EXTERNAL LONG CONSTANT tpu$_options,     &
                           tpu$_fileio,      &
                           tpu$_outputfile,  &
                           tpu$_commandfile, &
                           tpu$_sectionfile, &
                           tpu$_filename,    &
                           tpu$m_create,     &
                           tpu$m_command,    &
                           tpu$m_display,    &
                           tpu$m_output,     &
                           tpu$m_section

    MAP (fixed_buf) STRING output_file  = 255%, &
                           input_file   = 255%, &
                           command_file = 255%, &
                           section_file = 255%

    DECLARE LONG option_mask, bpv(1% TO 2%)

    !
    ! Define a structure for the item list.
    !
    RECORD item_list_3
        GROUP item(1% TO 15%)
            VARIANT
            CASE
                WORD buffer_length
                WORD item_code
                LONG buffer_address
                LONG return_address
            CASE
                LONG terminator
            END VARIANT
        END GROUP
    END RECORD
    DECLARE item_list_3 callback


    !
    ! Set the options.  This list of options will tell TPU
    ! that:
    !
    !     1) The default terminal should be used for the display.
    !     2) An output file will be generated when the user EXITs.
    !     3) A new input file will be created if the one specified
    !        does not exist.
    !     4) A command file will be specified.
    !     5) A section file will be specified.
    !
    ! Please note that TPU requires the use of a section file.  This
    ! must be either the default section file (EVE$SECTION.TPU$SECTION)
    ! or a personal section file (previously generated).
    !
    option_mask = tpu$m_display OR tpu$m_output  OR             &
                  tpu$m_create  OR tpu$m_command OR tpu$m_section

    !
    ! Set the input, output, and initialization file names.
    !
    input_file   = "TPU_INPUT_FILE.TXT"
    output_file  = "TPU_OUTPUT_FILE.TXT"
    command_file = "TPU_COMMAND_FILE.TPU"

    !
    ! Set the section file to be the VMS default.  This can be
    ! changed to point to a personal section file, if needed.
    !
    section_file = "SYS$SHARE:EVE$SECTION.TPU$SECTION"

    !
    ! Set the bpv array to point to 'fileio_routine'.  This will
    ! allow TPU to invoke a user-written function for every I/O
    ! operation necessary for the editing session.
    !
    bpv(1%) = LOC(fileio_routine)
    bpv(2%) = 0%

    !
    ! Initialize the item list.  This item list specifies to TPU
    ! what is desired.  This includes any files to be used in
    ! the startup process of the editor, files to be edited,
    ! and files to be output.  It also communicates to TPU
    ! that a user-written file I/O routine will be used for all
    ! I/O.
    !
    ! Additional items can be added, depending on what actions
    ! are desired.  See the documentation for Utility Routines
    ! (under TPU$INITIALIZE) for more information on the possible
    ! actions.
    !
    callback::item(1%)::buffer_length  = 4%
    callback::item(1%)::item_code      = tpu$_options
    callback::item(1%)::buffer_address = LOC(option_mask)
    callback::item(1%)::return_address = 0%

    callback::item(2%)::buffer_length  = LEN(TRM$(input_file))
    callback::item(2%)::item_code      = tpu$_filename
    callback::item(2%)::buffer_address = LOC(input_file)
    callback::item(2%)::return_address = 0%

    callback::item(3%)::buffer_length  = LEN(TRM$(output_file))
    callback::item(3%)::item_code      = tpu$_outputfile
    callback::item(3%)::buffer_address = LOC(output_file)
    callback::item(3%)::return_address = 0%

    callback::item(4%)::buffer_length  = LEN(TRM$(command_file))
    callback::item(4%)::item_code      = tpu$_commandfile
    callback::item(4%)::buffer_address = LOC(command_file)
    callback::item(4%)::return_address = 0%

    callback::item(5%)::buffer_length  = LEN(TRM$(section_file))
    callback::item(5%)::item_code      = tpu$_sectionfile
    callback::item(5%)::buffer_address = LOC(section_file)
    callback::item(5%)::return_address = 0%

    callback::item(6%)::buffer_length  = 4%
    callback::item(6%)::item_code      = tpu$_fileio
    callback::item(6%)::buffer_address = LOC(bpv(1%))
    callback::item(6%)::return_address = 0%

    callback::item(7%)::terminator     = 0%

    !
    ! Pass the address of the item list to VAXTPU as the return value
    ! for this function.
    !
    tpu_startup = LOC(callback)
END FUNCTION


16000	FUNCTION LONG fileio_routine (LONG 	co_de,   &
                              stream_structure 	str_eam, &
                              item_list_3      	da_ta)
    !
    ! This function will be called by VAXTPU for any file I/O
    ! necessary for the editing session.  It is invoked once
    ! for each I/O operation.  The structures received have
    ! information about what type of I/O operation should take
    ! place.
    !
    OPTION TYPE = EXPLICIT

    EXTERNAL LONG FUNCTION lib$scopy_dxdx,          &
                           lib$scopy_r_dx,          &
                           lib$movc3,               &
                           tpu$message

    EXTERNAL LONG CONSTANT rms$_normal

    RECORD stream_structure
        LONG fid
        WORD alq
        BYTE rat
        BYTE rfm
        WORD lng
        BYTE tpe
        BYTE cls
        LONG adr
    END RECORD

    RECORD item_list_3
        VARIANT
        CASE
            GROUP item(1% TO 15%)
                VARIANT
                CASE
                    WORD buflen
                    WORD itmcod
                    LONG bufadr
                    LONG retlen
                CASE
                    LONG terminator
                END VARIANT
            END GROUP
        CASE
            WORD dlen
            BYTE dtype
            BYTE dclass
            LONG daddr
        END VARIANT
    END RECORD

    EXTERNAL LONG CONSTANT tpu$k_open,         &
                           tpu$k_close,        &
                           tpu$k_close_delete, &
                           tpu$k_get,          &
                           tpu$k_put,          &
                           tpu$k_filename,     &
                           tpu$k_access,       &
                           tpu$k_io,           &
                           tpu$k_input,        &
                           tpu$k_output,       &
                           tpu$_failure

    DECLARE LONG           stat,         &
                           cntr,         &
                           return_value, &
                           file_id,      &
                           file_access

    DECLARE STRING         the_record,   &
                           file_name

    !
    ! This array is used to keep track of what channel(s)
    ! the fileio routine is using.  By putting the array into
    ! a map, the values will be retained between invocations
    ! of the function.  This is necessary because more than
    ! one file can be accessed during the a TPU editing session.
    !
    MAP (open_files) LONG channel_array(1% TO 119%)

    WHEN ERROR IN
        file_id = 1%
        !
        ! Use the code value passed to this routine by VAXTPU to
        ! determine what action must be taken.
        !
        SELECT co_de
            CASE = tpu$k_open
                !
                ! The action to be taken is to open a file.
                !

                !
                ! Find an available VAX BASIC channel number.
                !
                UNTIL channel_array(file_id) = 0%
                    file_id = file_id + 1%
                    IF file_id > 119% THEN
                        !
                        ! Note:  The VAX BASIC channel number
                        !        cannot exceed 119, but up to
                        !        512 is specified in the TPU
                        !        documentation.  119 is used
                        !        as the limit for this program.
                        !
                        stat = tpu$message ("Unable to complete operation...")
                        CALL lib$stop (stat BY VALUE) IF (stat AND 1%) = 0%

                        stat = tpu$message ("...no more channels available")
                        CALL lib$stop (stat BY VALUE) IF (stat AND 1%) = 0%

                        return_value = rms$_normal
                        GO TO end_fct
                    END IF
                NEXT

                channel_array(file_id) = 1%
                str_eam::fid = file_id

                !
                ! Determine how many item codes are used in the list (find
                ! the part of the item list representing the terminator).
                ! The item codes will give more detail on the type
                ! of OPEN operation is to be performed.
                !
                ! Please note that this program does not check for
                ! all possible item codes.  It merely checks for
                ! the item codes expected given the context this
                ! program was designed to run under.  Additional
                ! item codes can be added if needed.
                !
                cntr = 1%
                UNTIL da_ta::item(cntr)::terminator = 0%
                    !
                    ! Evaluate the item list for information pertinent to
                    ! opening the file.  The item codes direct what should
                    ! be done and what each section of the item list
                    ! represents.  Other item codes can be added for
                    ! additional functionality.
                    !
                    IF da_ta::item(cntr)::itmcod = tpu$k_filename THEN
                        !
                        ! This item code represents the file to be
                        ! opened.  Use LIB$SCOPY_R_DX to extract the
                        ! file from the memory location pointed to by
                        ! this section of the item list to a string
                        ! variable name that can be used in an OPEN
                        ! statement.
                        !
                        stat = lib$scopy_r_dx                            &
                                    (da_ta::item(cntr)::buflen,          &
                                     da_ta::item(cntr)::bufadr BY VALUE, &
                                     file_name)
                        CALL lib$stop (stat BY VALUE) IF (stat AND 1%) = 0%
                    END IF

                    IF da_ta::item(cntr)::itmcod = tpu$k_access THEN
                        !
                        ! This section of the item list points to a
                        ! value representing how the file should be
                        ! opened.  Use LIB$MOVC3 to place the information
                        ! into a longword which can be used to derive
                        ! this information.
                        !
                        stat = lib$movc3 (da_ta::item(cntr)::buflen, &
                                          da_ta::item(cntr)::bufadr, &
                                          file_access)
                        CALL lib$stop (stat BY VALUE) IF (stat AND 1%) = 0%
                    END IF

                    cntr = cntr + 1%
                NEXT

                !
                ! Open the file based on the access mode given by
                ! VAXTPU.
                !
                SELECT file_access
                    CASE = tpu$k_io
                        OPEN file_name AS FILE #file_id
                    CASE = tpu$k_input
                        OPEN file_name FOR INPUT AS FILE #file_id
                    CASE = tpu$k_output
                        OPEN file_name FOR OUTPUT AS FILE #file_id
                    CASE ELSE
                        PRINT "Unexpected access given.  Aborting";
                        PRINT " function.  Value given was:"; file_access
                        return_value = tpu$_failure
                        GO TO end_fct
                END SELECT

                !
                ! Place information about the opened file into the
                ! 'stream' structure.  This will be useful in
                ! subsequent invocations of this function.
                !
                stat = lib$scopy_dxdx (file_name, str_eam::lng)
                CALL lib$stop (stat BY VALUE) IF (stat AND 1%) = 0%

            CASE = tpu$k_close
                !
                ! Close the file and clear the switch representing
                ! its channel.
                !
                CLOSE #str_eam::fid
                channel_array(str_eam::fid) = 0%

            CASE = tpu$k_close_delete
                !
                ! Close the file, delete it, and clear the switch
                ! representing its channel.  The file name must
                ! be derived from the 'data' structure before it
                ! can be deleted.
                !
                CLOSE #str_eam::fid
                stat = lib$scopy_r_dx (da_ta::item(cntr)::buflen,          &
                                       da_ta::item(cntr)::bufadr BY VALUE, &
                                       file_name)
                CALL lib$stop (stat BY VALUE) IF (stat AND 1%) = 0%
                KILL file_name
                channel_array(str_eam::fid) = 0%
                PRINT "'"; file_name; "' was deleted."

            CASE = tpu$k_get
                !
                ! Retrieve the (next) record from the file.
                !
                GET #str_eam::fid
                MOVE FROM #str_eam::fid, the_record = RECOUNT

                !
                ! Load the 'data' structure with the information
                ! about the record just retrieved so that VAXTPU
                ! knows where to find it.  This can be done
                ! with LIB$SCOPY_DXDX.
                !
                stat = lib$scopy_dxdx (the_record, da_ta::dlen)
                CALL lib$stop (stat BY VALUE) IF (stat AND 1%) = 0%

            CASE = tpu$k_put
                !
                ! Write the record passed to this function by
                ! VAXTPU to the file.  The information about the
                ! record is stored in the 'data' structure.
                ! LIB$SCOPY_DXDX can be used to extract that
                ! data into a string variable which can be written
                ! to the file.
                !
                stat = lib$scopy_dxdx (da_ta::dlen, the_record)
                CALL lib$stop (stat BY VALUE) IF (stat AND 1%) = 0%

                PRINT #str_eam::fid, LEFT$(the_record, da_ta::dlen)
        END SELECT

        return_value = rms$_normal
    USE
        !
        ! NOTE:   More robust error handling can be added to account
        !         for additional errors/conditions.
        !
        return_value = RMSSTATUS(1%, VALUE)
    END WHEN
    end_fct:
END FUNCTION return_value


    
    $!========================================================================
    $ create read_file.bas
    
1	PROGRAM read_file
    
    OPTION TYPE = EXPLICIT

    DECLARE LONG           i%

    DECLARE STRING 	   rec_string


    OPEN "TPU_OUTPUT_FILE.TXT" FOR INPUT AS FILE 2%, RECORDSIZE 70%

	FOR i% = 0% STEP 1% WHILE -1%
		WHEN ERROR IN
			INPUT #2%, rec_string
		USE
			EXIT HANDLER	IF ERR <> 11%
			print
			print
			print "eof trapped"
			continue 10000
		END WHEN
		print rec_string
	NEXT i%
	print
	print
	print 'eof NOT trapped'
	goto 10000

 10000	print 'done'
	
 	END PROGRAM
    
    $ bas callable_tpu
    $ bas read_file
    $ link callable_tpu
    $ link read_file
    $ run callable_tpu
    $ run read_file
T.RTitleUserPersonal
Name
DateLines
1944.1its not pretty in thereHNDYMN::MCCARTHYA Quinn Martin ProductionSat Apr 05 1997 21:0325
This is VAX right?  

Having seen the "condition handling" of BASRTL, I am shocked when any 
type of error handling of standard OpenVMS conditions works.  

I'm a little confused in the sequence of events.  

- TPU was running and is now "done"
- The BASIC program is trying to read (Via INPUT) the file that TPU created
- When (no pun intended) the INPUT statement from within the WHEN block
  reads the last line of that file, it dies.

I can only suggest using the the debugger and seeing what the 
condition handlers are on the stack.  I can guess what is happening
is that lib$revert cancels the BAS$HANDLER and not the TPU$HANDLER.  Actually,
is lib$establish even supported when using WHEN blocks in BASIC?  

Since the address of the condition handler is thrown in the frame, when
you call lib$establish for TPU$HANDLER, you wipe out the BAS$HANDLER one -
check this using the SHOW FRAME command in the debugger.  

Possible solution is to do a lib$establish(bas$handler) instead of 
lib$revert - just a WAG though.

bjm