Google
 

Trailing-Edge - PDP-10 Archives - BB-L054E-RK - apxcmd.b36
There are no other files named apxcmd.b36 in the archive.
MODULE APXCMD (
		LANGUAGE(BLISS36),
		ENTRY (
			GET_COMMAND,
			GET_YES_NO,
			SET_LN,
			READ_FILE
				)
		) =
BEGIN
 
!
!		       COPYRIGHT (c) 1980 BY
!	    Digital Equipment Corporation, Maynard, MA.
!
!   This software is furnished under a license and may be  used
!   and  copied  only  in  accordance  with  the  terms of such
!   license and with  the  inclusion  of  the  above  copyright
!   notice.   This software or any other copies thereof may not
!   be provided  or  otherwise	made  available  to  any  other
!   person.   No  title  to  and  ownership  of the software is
!   hereby transferred.
!
!   The information in	this  software	is  subject  to  change
!   without  notice and should not be construed as a commitment
!   by Digital Equipment Corporation.
!
!   Digital  assumes  no  responsibility   for	 the   use   or
!   reliability  of  its  software  on	equipment  which is not
!   supplied by Digital.
!
 
!++
! FACILITY:
!    Autopatch Exec Command Parser Support Module
!
! ABSTRACT:
!
!
!
!
! ENVIRONMENT: TOPS-20 / TOPS-10
!
! AUTHOR: Donald R. Brandt, CREATION DATE: 1 May 1980
!
! MODIFIED BY:
!
!	Revision history follows
!
!--

!
! Edit History for APXCMD
!
! CMD001  by DRB on 13-Oct-80
!   Added routine GET_YES_NO to allow yes/no responses.
!
! CMD002  by DRB on 11-Nov-80
!   Changed SET_LN so that defn returned is always upper case.
!

GLOBAL BIND EDTCMD = %O'02' ;		! Edit level of this module
 
!
! TABLE OF CONTENTS:
!
 
FORWARD ROUTINE
 
	GET_COMMAND,
	GET_YES_NO,
	SET_LN,
	READ_FILE ;
 
 
!
! INCLUDE FILES:
!
 
LIBRARY 'BLI:TENDEF'	;		!PDP-10 Definitions
LIBRARY 'BLI:MONSYM'	;		!TOPS-20 Monitor Symbols
LIBRARY 'APEX'		;		!APEX macros
LIBRARY 'BLSPAR'	;		!BLISS parser macros
LIBRARY 'DEBUG'		;		!Debugging macros
 
 
!
! EXTERNAL REFERENCES:
!

GLOBAL BIND EDTAPX = APEX_EDT ;		! Edit level of APEX.R36

 
EXTERNAL
    TAKFDB:	PDB_BLOCK ;		!PDB for TAKE command
					! (defined in OPRPAR)

!
!  The BLISS interface routines to GALAXY parser routines
!   These are defined in BLSPAR.B36
!
 
EXTERNAL ROUTINE $PRINIT ;		!Library Initialization
EXTERNAL ROUTINE $PRCMND ;		!Parse command
EXTERNAL ROUTINE $PARSE ;		!Parse command
EXTERNAL ROUTINE $P$TAKE ;		!Setup for TAKE
EXTERNAL ROUTINE $PRSETUP ;		!Setup after parse
EXTERNAL ROUTINE $PRNFLD ;		!Return next field type
EXTERNAL ROUTINE $PRKEY ;		!Return keyword
EXTERNAL ROUTINE $PRNUM ;		! number
EXTERNAL ROUTINE $PRSWI ;		! switch value
EXTERNAL ROUTINE $PRFIL ;		! file spec
EXTERNAL ROUTINE $PRFLD ;		! character field
EXTERNAL ROUTINE $PRCFM ;		! confirmation (CRLF)
EXTERNAL ROUTINE $PRDIR ;		! directory
EXTERNAL ROUTINE $PRUSR ;		! user name
EXTERNAL ROUTINE $PRCMA ;		! comma
EXTERNAL ROUTINE $PRFLT ;		! floating point number
EXTERNAL ROUTINE $PRDEV ;		! device name
EXTERNAL ROUTINE $PRTXT ;		! text to EOL
EXTERNAL ROUTINE $PRTAD ;		! time and date
EXTERNAL ROUTINE $PRQST ;		! quoted string
EXTERNAL ROUTINE $PRUNQ ;		! unquoted string
EXTERNAL ROUTINE $PRTOK ;		! token
EXTERNAL ROUTINE $PRNUX ;		! digits terminated by nondigit
EXTERNAL ROUTINE $PRACT ;		! account string
EXTERNAL ROUTINE $PRNOD ;		! node name
EXTERNAL ROUTINE $PRSXF ;		! sixbit field
 
 
!
! EXTERNAL REFERENCES CONTINUED:
!
 
!
!  The BLISS interface routines to the GALAXY library
!   These are defined in BLSGLX.B36
!
 
EXTERNAL ROUTINE $F_FD	;		!Return FD for a file
EXTERNAL ROUTINE $K_SOUT ;		!String output routine
EXTERNAL ROUTINE $M_GMEM ;		!Memory allocation routine
EXTERNAL ROUTINE $M_RMEM ;		!Memory deallocation routine
EXTERNAL ROUTINE $FMT$FD ;		!Format name from FD for a file
EXTERNAL ROUTINE $FMT$NUM ;		!Format number
EXTERNAL ROUTINE $DEF$LN ;		!Define logical name
EXTERNAL ROUTINE $GET$LND ;		!Get logical name definition
 
!
!  APEX support routines
!
 
EXTERNAL ROUTINE CLOSE ;		!CLOSE a file
EXTERNAL ROUTINE R_REL ;		!Reset/release a file
EXTERNAL ROUTINE T_LOOKUP ;		!Lookup entry in a table
 
!
! MACROS:
!
 
!
! EQUATED SYMBOLS:
!
 
!
!  Make forward references for PDB's using the
!   special macro provided
!
 
$PDB (LNDINI,
      LNDTXT,
      LNDCFM,
      YONINI,
      YONKEY,
      YONCFM) ;
 
!
!  Make forward reference for keyword tables
!    note allocation is # entries + 1
!
 
FORWARD
    YONTAB:	VECTOR[3] ;

!
!  Define YES/NO response values
!

LITERAL
    $$NO  = 1,
    $$YES = 2 ;

 
!
! OWN STORAGE:
!
!
!   Syntax tree for logical name definition
!

OWN
    LNDINI:	$INIT(NEXT=LNDTXT),
    LNDTXT:	$TEXT(NEXT=LNDCFM,		! Text string
		      FLAGS=cm_sdh OR cm_dpp,	! Suppress default help
						! Default supplied
		      HELP= 'Enter structure and directory to define logical name'),
    LNDCFM:	$CONFIRM() ;
 
!
!   Syntax tree for YES / NO response
!

OWN
    YONINI:	$INIT(NEXT=YONKEY),
    YONKEY:	$KEY(NEXT=YONCFM,		! Keyword
		     TABLE=YONTAB,
		      FLAGS=cm_sdh OR cm_dpp,	! Suppress default help
						! Default supplied
		      HELP= 'Enter YES or NO'),
    YONCFM:	$CONFIRM() ;
 

!
!   Keyword table of YES/NO responses
!

OWN
    YONTAB:	$KEYTAB((('NO',$$NO),
			('YES',$$YES))) ;
GLOBAL ROUTINE GET_COMMAND(prompt,command,syntax_tree,cp_routine) =	

!++
! FUNCTIONAL DESCRIPTION:
!
!   This routine gets a command, parses it,  and  then  invokes
!   any  processing  associated  with the command.  The command
!   can be a string already stored in  memory,  or  it  can  be
!   input  from  the  terminal.  A syntax tree must be supplied
!   that describes the syntax for all valid commands.
!
!   This routine first invokes the GALAXY parser  which  parses
!   the command using this syntax tree.  Following a successful
!   parse, a  list  of  values  corresponding  to  the  various
!   command parameters is available.  This routine then invokes
!   a command processing routine to pick up  the  parsed  items
!   and process them accordingly.
!
! FORMAL PARAMETERS:
!
!	prompt:	A BLISS character pointer to the prompt string.
!
!	command:
!		A BLISS character pointer to a command string
!		in memory. (0 if command is from TTY:)
!
!	syntax_tree:
!		the address of the top node of the syntax tree
!		giving the syntax of the commands.
!
!	cp_routine:
!		the name of the routine to call to process a
!		command line following a successful parse.
!
! IMPLICIT INPUTS:
!
!	None
!
! IMPLICIT OUTPUTS:
!
!	None
!
! ROUTINE VALUE:
!
!	Returns TRUE if no errors.
!	Returns FALSE if the parser or cp_routine fails
!
! SIDE EFFECTS:
!
!   Side effects may be included in the command syntax tree  or
!   the command processing routine.
!
!--

    BEGIN				!Beginning ROUTINE GET_COMMAND

    LOCAL
	error_flag,
	error_msg ;

    $TRACE('Beginning','GET_COMMAND') ;

    IF $PARSE(.syntax_tree,.prompt,.command,error_msg,error_flag)
    THEN
 	(.cp_routine) ()
    ELSE
	( TTY(.error_msg) ; false )
    END ;				 !End of GET_COMMAND
 
GLOBAL ROUTINE GET_YES_NO(prompt,yon_def) =	

!++
! FUNCTIONAL DESCRIPTION:
!
!   Accept a YES or NO response.  This routine does not  return
!   control until a valid response is given.
!
! FORMAL PARAMETERS:
!
!	prompt:	A BLISS character pointer to the prompt string.
!
!	yon_def:
!		the address of ASCIZ string giving default response
!
! IMPLICIT INPUTS:
!
!	None
!
! IMPLICIT OUTPUTS:
!
!   Outputs any associated error messages
!
! ROUTINE VALUE:
!
!	Returns TRUE if response is YES.
!	Returns FALSE if response is NO.
!
! SIDE EFFECTS:
!
!	None
!
!--

    BEGIN				!Beginning ROUTINE GET_YES_NO

    LOCAL
	c,
	t,
	error_flag,
	error_msg ;

    $TRACE('Beginning','GET_YES_NO') ;

    WHILE true DO
	BEGIN
	yonkey[PDB_DEF] = CH$PTR(.yon_def) ;
	IF $PARSE(yonini,.prompt,0,error_msg,error_flag)
	THEN
	    BEGIN
	    $PRKEY(t,c) ;
	    SELECTONE .c OF
		SET
		[$$NO]:		RETURN false ;
		[$$YES]:	RETURN true ;
		TES ;
	    END
	ELSE
	    TTY(('?Type YES or NO'))
	END

    END ;				 !End of GET_YES_NO
 
GLOBAL ROUTINE SET_LN(prompt,ln_adr,lnd_adr,lnd_def) =	

!++
! FUNCTIONAL DESCRIPTION:
!
!   Setup a logical name definition.   This  routine  does  not
!   return until a valid logical name definition is entered.
!
! FORMAL PARAMETERS:
!
!	prompt:	A BLISS character pointer to the prompt string.
!
!	ln_adr:	The address of ASCIZ string specifying logical name
!
!	lnd_adr:
!		the address to return the address of the logical
!		 name definition in
!
!	lnd_def:
!		the address of ASCIZ string giving default definition
!
! IMPLICIT INPUTS:
!
!	None
!
! IMPLICIT OUTPUTS:
!
!   Outputs any associated error messages
!
! ROUTINE VALUE:
!
!	Always returns TRUE.
!
! SIDE EFFECTS:
!
!   The logical name is defined.
!
!--

    BEGIN				!Beginning ROUTINE SET_LN

    LOCAL
	a,
	c,
	t,
	address,
	error,
	error_flag,
	error_msg ;

    $TRACE('Beginning','SET_LN') ;

    WHILE true DO
	BEGIN
	lndtxt[PDB_DEF] = CH$PTR(.lnd_def) ;
	IF $PARSE(lndini,.prompt,0,error_msg,error_flag)
	THEN
	    BEGIN
	    $PM($PRTXT(t,a,c),.lnd_adr) ;
	    IF $DEF$LN(.ln_adr,.(.lnd_adr),error)
	    THEN
		BEGIN
		$GET$LND(.ln_adr,address,error) ;
		.lnd_adr = COPY_STR(.address) ;
		RETURN true
		END
	    ELSE
		$ERROR(W$CDL,*,.ln_adr,S(' to be '),.(.lnd_adr),
		  S(cr_lf,' ('),.error,S(')'))
	    END
	ELSE
	    TTY(.error_msg)
	END

    END ;				 !End of SET_LN
 
GLOBAL ROUTINE READ_FILE(file,syntax_tree,cp_routine,er_routine) =	

!++
! FUNCTIONAL DESCRIPTION:
!
!   This routine reads and processes a text file of commands.
!
! FORMAL PARAMETERS:
!
!	file:	the address of the file descriptor (FILE$$)
!		 specifying the file to be read
!
!	syntax_tree:
!		the address of the top node of the syntax tree
!		 giving the syntax of commands in the file.
!
!	cp_routine:
!		the name of the routine to call to process a
!		 command line following a successful parse.
!
!	er_routine:
!		the name of a routine to call to process an
!		 error in a command line
!
! IMPLICIT INPUTS:
!
!	None
!
! IMPLICIT OUTPUTS:
!
!	None
!
! ROUTINE VALUE:
!
!	Returns TRUE if no errors.
!	Returns FALSE if an error is encountered in the file.
!
! SIDE EFFECTS:
!
!   Same side  effects  as  the  specified  command  processing
!   routine.
!
!--

    BEGIN				!Beginning ROUTINE READ_FILE

    LOCAL
	error_flag:	PAR_FLAG,
	error_msg,
	ifn1,
	ifn2,
	line,
	return_value,
	return_code ;
    MAP
	file:	REF FILE$$ ;

    $TRACE('Beginning','READ_FILE') ;

    CK_DATATYPE(file,FILE) ;

    IF NOT $P$TAKE(.file[FILE_FD],0,ifn1,ifn2)	! Setup to do a TAKE
    THEN
	RETURN $ERROR(W$IFR,*,FMT_FILE(file)) ;
    
    return_value = true ;
    line = 0 ;
    WHILE true DO				! Loop until EOF
	BEGIN
	line = .line + 1 ;
	IF $PARSE(.syntax_tree,0,0,error_msg,error_flag)
        THEN
    	    return_code = (.cp_routine) ()
        ELSE
	    BEGIN
	    IF .error_flag[FLG_ENDT]
	    THEN
	        RETURN .return_value
	    ELSE
		return_code = (.er_routine) (.file,.line,.error_msg)
	    END ;
	IF .return_code EQL false
	THEN
	    return_value = false
	END

    END ;				!End ROUTINE READ_FILE

 
END
 
ELUDOM