Google
 

Trailing-Edge - PDP-10 Archives - DEC_CMS-20_V1.0_SRC - cms/sources/params.bli
There are no other files named params.bli in the archive.
module params (	! Recognize and parse parameters of a CMS command string.
		ident = '1',
		%if
		    %bliss(bliss32)
		%then
		    language(bliss32),
		    addressing_mode(external=long_relative,
				    nonexternal=long_relative)
		%else
		    language(bliss36)
		%fi
		) =
begin

!
!			  COPYRIGHT (C) 1982 BY
!	      DIGITAL EQUIPMENT CORPORATION, MAYNARD, MASS.
!
! 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:  CMS Library Processor
!
! Abstract:
!
!	This module contains routines that analyze parameters of CMS
!	commands.  The principal routine, RECPAR, analyzes some parameters
!	itself, and calls other routines of this module to analyze others.
!
! Environment:  Transportable
!
! Author:  Earl Van Horn	Creation Date:  April, 1979
!
!--
!
! Table of Contents:
!
forward routine
    chk_name_type,		! Check the syntax of a file name and type.
    clsnam,			! Check the syntax of a class name.
    extend_text : novalue,	! Extend a descriptor to encompass a string.
    genexp,			! Recognize and parse a generation expression.
    gennum,			! Check the syntax of a generation number.
    genpri,			! Check the syntax of a generation primary.
    node_desc_init : novalue,	! Initialize a node component descriptor.
    prevbl,			! See if the previous char. is a space or tab.
    recpar,			! Recognize and parse any parameter.
    wild_element_ref ;		! Recognize element reference with wild cards.

!
! Include Files:
!

%if %bliss(bliss32) %then
library 'sys$library:starlet';
%fi

%if %bliss(bliss36) %then
require 'jsys:';
%fi

library 'XPORT:' ;
require 'BLISSX:' ;
require 'COMUSR:' ;		! Declarations for the user of the language
				! processor.
require 'LANGME:' ;		! Declarations internal to the language
				! processor.

!
! Macros:
!

!
! Equated Symbols:
!
literal
    k_max_file_name = %bliss32(9) %bliss36(39) %bliss16(6),
				! Maximum number of characters in a file
				! name component.
    k_max_file_type = %bliss32(3) %bliss36(39) %bliss16(3) ;
				! Maximum number of characters in a file type.

!
! Own Storage:
!

!
! External References:
!

external literal
    s_badpri,
    s_badvar,
    s_badwild,
    s_fttoolong,		!in description, the file type is too long.
    s_nmtoolong,		!in description, the name Lexeme is too long.
    s_nameinv,			! class name must begin with alphabetic
    s_nodot,
    s_nolevel,
    s_nospace,
    s_onedot,
    s_onlyone;

external
    comzon ;			! Zone for allocating command processor stuff.

external routine
    ask,
    bldcom,
    bug,			! Report a bug.
    codspl,			! Get the spelling for lexical or grammar code.
    ers,			! Report a user mistake.
    errchr,			! Report an erroneous character.
    nxtlex,			! Identify next lexeme in the command string.
    peekch,			! Peek ahead to the next character.
    zalloc ;			! Allocate storage.
routine chk_name_type(a_lexeme, a_description) =

!++
! Functional Description:
!
!	This routine checks that the given lexeme is a valid extended file
!	name, i.e., one that consists of a non-null file name component,
!	optionally followed by a period and a possibly null file type.
!	The routine returns TRUE if the lexeme is valid.  The given description
!	is a phrase describing what the lexeme is supposed to be, for use
!	in error messages.
!
! Formal Parameters:
!
!	a_lexeme:	Address of a descriptor for the lexeme to be checked.
!			The lexeme must have non-zero length.
!	a_description:	Address of a descriptor for a phrase describing
!			the lexeme, for use in error messages.
!
! Implicit Inputs:
!
!	None
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE if the lexeme is valid, otherwise FALSE.
!
! Side Effects:
!
!	None
!
!--

    begin	! CHK_NAME_TYPE
    bind
	lexeme = .a_lexeme : desc_block,
	description = .a_description : desc_block ;

    local
	dot_x,			! Zero-origined position of any dot within
				! the lexeme.  -1 means no dot found.
	p_this ;		! Character pointer to current character.

    ! Make sure the lexeme is non-empty.
    if .lexeme[desc_len] eql 0
    then
	bug(cat(('CHK_NAME_TYPE was given an empty '), description)) ;

    ! Check each character.
    dot_x = -1 ;
    p_this = .lexeme[desc_ptr] ;
    incr i from 1 to .lexeme[desc_len] do
	begin	! Check one character and advance.
	selectone ch$rchar(.p_this) of
	    set		! Check one character.

	    [%c'A' to %c'Z', %c'0' to %c'9']:
		;	! Nothing.

    ! TOPS-20 allows hyphens, underscores and dollar signs as part 
    ! of a legal file specification
      
    %if %bliss(bliss36) %then
	%if %switches(tops20) %then
	
	     [%c'_',%c'-',%c'$']:
		;	! Nothing	
	%else
	      %error('DS-10 support not implemented')
	%fi
    %fi

	    [%c'.']:
		if .dot_x eql -1
		then
		    dot_x = .i - 1
		else
		    begin	! Too many dots.
		    ers(s_onlyone,cat('In ',description,', the name ', lexeme,
				' may have at most one period')) ;
		    return false ;
		    end ;	! Too many dots.

	    [otherwise]:
		begin	! Invalid character.
		errchr(.p_this, lexeme, description) ;
		return false ;
		end ;	! Invalid character.

	    tes ;	! Check one character.

	p_this = ch$plus(.p_this, 1) ;
	end ;	! Check one character and advance.

    ! Check for some errors.
    if .dot_x eql -1
    then
	begin	! Dot is required in this release.
	ers(s_onedot,cat('In ',description,', the name ',lexeme,
		' must include or end with a period')) ;
	return false ;
	end ;	! Dot is required in this release.
    if .dot_x eql 0
    then
	begin	! Leading dot.
	ers(s_nodot,cat('In ',description, ', the name ',lexeme,
		' may not begin with a period')) ;
	return false ;
	end ;	! Leading dot.
    if .dot_x gtr k_max_file_name
    then
	begin	! File name too long.
	ers(s_nmtoolong,cat('In ', description, ', the name ',
		(.dot_x, .lexeme[desc_ptr]), ' is too long')) ;
	return false ;
	end ;	! File name too long.
    if .lexeme[desc_len] - .dot_x - 1 gtr k_max_file_type
    then
	begin	! File type too long.
	ers(s_fttoolong,cat('In ', description, ', the file type ',
		(.lexeme[desc_len] - .dot_x - 1,
				ch$plus(.lexeme[desc_ptr], .dot_x + 1)),
		' is too long')) ;
	return false ;
	end ;	! File type too long.

    true
    end ;	! CHK_NAME_TYPE
global routine clsnam(a_lexeme, a_description) =

!++
! Functional Description:
!
!	This routine checks that the given lexeme is a valid class or group
!	name, and returns TRUE if it is.  The given description is a phrase
!	describing what the lexeme is supposed to be, for use in error
!	messages.
!
! Formal Parameters:
!
!	a_lexeme:	Address of a descriptor for the lexeme to be checked.
!			The lexeme must have non-zero length.
!	a_description:	Address of a descriptor for a phrase describing
!			the lexeme, for use in error messages.
!
! Implicit Inputs:
!
!	None
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE if the lexeme is valid, otherwise FALSE.
!
! Side Effects:
!
!	None
!
!--

    begin	! CLSNAM
    bind
	lexeme = .a_lexeme : desc_block,
	description = .a_description : desc_block ;

    local
	p_this ;		! Character pointer to current character.

    ! Make sure the lexeme is non-empty.
    if .lexeme[desc_len] eql 0
    then
	bug(cat('CLSNAM was given an empty ', description)) ;

    ! Enforce a length restriction.
    if .lexeme[desc_len] gtr 31
    then
	begin	! Too long.
	ers(s_nmtoolong,cat('In ',description,', the name ',lexeme,
		' is too long')) ;
	return false ;
	end ;	! Too long.

    ! Check first character.
    p_this = .lexeme[desc_ptr] ;
    if ch$rchar(.p_this) lss %c'A'   or
       ch$rchar(.p_this) gtr %c'z'
    then
	begin 	! leading digit error
	    ers(s_nameinv,cat('Error in ',lexeme,'; ',description,
			's must begin with an alphabetic character'));
	    return false;
	end;	!leading digit error

    ! check subsequent characters
    incr i from 2 to .lexeme[desc_len] do
	begin	! Advance and check one character 
	p_this = ch$plus(.p_this, 1) ;
	selectone ch$rchar(.p_this) of
	    set		! Check one character.

	    [%c'A' to %c'Z', %c'0' to %c'9', %c'$', %c'_', %c'.']:
		;		! Accept any of these characters anywhere.

	    [otherwise]:
		begin		! Invalid character.
		errchr(.p_this, lexeme, description) ;
		return false ;
		end ;		! Invalid character.
	    tes ;	! Check one character.

	end ;	! Advance and check one character 

    true
    end ;	! CLSNAM
routine extend_text(a_extendable, a_last) : novalue =

!++
! Functional Description:
!
!	This routine changes the length of a given string descriptor so
!	that the denoted string ends with the last character of the
!	string denoted by a second descriptor.  The second string must
!	not be empty and must not begin before the first begins.
!
! Formal Parameters:
!
!	a_extendable:	Address of a descriptor whose length will be changed.
!	a_last:		Address of a descriptor of a non-empty string whose
!			last character will become the last character of
!			of the string denonted by the extendable descriptor.
!
! Implicit Inputs:
!
!	None
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	None
!
! Side Effects:
!
!	None
!
!--

    begin	! EXTEND_TEXT
    bind
	extendable = .a_extendable : desc_block,
	last = .a_last : desc_block ;

    if last[desc_len] eql 0
    then
	bug(cat(('Extension of '), extendable, (' is empty'))) ;

    if ch$diff(.last[desc_ptr], .extendable[desc_ptr]) lss 0
    then
	bug(cat(last, (' occurs before '), extendable)) ;

    extendable[desc_len] =
	ch$diff(.last[desc_ptr], .extendable[desc_ptr]) + .last[desc_len] ;

    end ;	! EXTEND_TEXT
global routine genexp(a_user_string, syntax, a_text, a_a_tree) =

!++
! Functional Description:
!
!	This routine recognizes a generation expression.  It gets the
!	expression by calling NXTLEX, checks that it has proper form,
!	initializes a descriptor for its text, and constructs a tree node
!	as described in COMUSR.REQ.
!
! Formal Parameters:
!
!	a_user_string:	Address of a descriptor for the user string at the
!			beginning of which the generation expression is to be
!			recognized.  This descriptor will be updated to denote
!			the user string following the generation expression, by
!			calling NXTLEX.
!	syntax:		The integer code for the syntactic construct to be
!			recognized by this routine, usually K_GEN_EXP_SYN.
!	a_text:		Address of a descriptor to be initialized to denote
!			this generation expression.
!	a_a_tree:	Address of a fullword to receive the address of a
!			node block, which will be initialized as described in
!			COMUSR.REQ.  If no node block is created, the fullword
!			will be set to K_NULL.
!
! Implicit Inputs:
!
!	None
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE if the user made no mistake, otherwise FALSE.
!
! Side Effects:
!
!	Storage for a parse tree node may be allocated in COMZON using ZALLOC.
!
!--

    begin	! GENEXP
    bind
	user_string = .a_user_string : desc_block,
	text = .a_text : desc_block,
	r_tree = .a_a_tree : ref node_block ;
    local
	primary : desc_block ;		! The generation primary part.

    ! Get the text of the expression, which in this release is a single lexeme.
    if not nxtlex(user_string, k_normal_lex, codspl(.syntax), text)
    then
	return false ;

    ! Find the generation primary.
    $str_desc_init(descriptor = primary, string = text) ;
    if %c'+' eql ch$rchar(ch$plus(.text[desc_ptr], .text[desc_len] - 1))
    then
	primary[desc_len] = .text[desc_len] - 1 ;

    ! Make sure the primary is good.
    if .primary[desc_len] eql 0
    then
	begin	! Missing primary.
	ers(s_badpri,cat('In ',codspl(.syntax),', the name ',text,
		 ' must begin with ',codspl(k_gen_pri_syn))) ;
	return false ;
	end ;	! Missing primary.
    if not genpri(primary, codspl(k_gen_pri_syn))
    then
	return false ;

    ! Create a parse tree node if there is a plus operator.
    if .text[desc_len] neq .primary[desc_len]
    then
	begin	! Plus present.
	r_tree = zalloc(k_nod_units, comzon) ;
	r_tree[nod_syntax] = .syntax ;
	r_tree[nod_branches] = 2 ;
	$str_desc_init(descriptor = r_tree[nod_desc_1], string = primary) ;
	$str_desc_init(descriptor = r_tree[nod_desc_2],
	       string = (1, ch$plus(.text[desc_ptr], .text[desc_len] - 1))) ;
	end	! Plus present.
    else
	r_tree = k_null ;

    true    
    end ;	! GENEXP
global routine genpri(a_lexeme, a_description) =

!++
! Functional Description:
!
!	This routine checks that the given lexeme is a valid generation
!	primary, and returns TRUE if it is.  The given description is
!	a phrase describing what the lexeme is supposed to be, for use
!	in error messages.
!
! Formal Parameters:
!
!	a_lexeme:	Address of a descriptor for the lexeme to be checked.
!			The lexeme must have non-zero length.
!	a_description:	Address of a descriptor for a phrase describing
!			the lexeme, for use in error messages.
!
! Implicit Inputs:
!
!	None
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE if the lexeme is valid, otherwise FALSE.
!
! Side Effects:
!
!	None
!
!--

    begin	! GENPRI
    bind
	lexeme = .a_lexeme : desc_block,
	description = .a_description : desc_block ;

    selectone ch$rchar(.lexeme[desc_ptr]) of
	set	! Dispatch on first character.

	[%c'0' to %c'9']:
	    if not gennum(lexeme, codspl(k_gen_num_syn))
	    then
		return false ;

	[%c'A' to %c'Z', %c'a' to %c'z', %c'_', %c'.']:
	    if not clsnam(lexeme, codspl(k_cls_name_syn))
	    then
		return false ;

	[otherwise]:
	    begin	! Bad first character.
	    errchr(.lexeme[desc_ptr], lexeme, description) ;
	    return false ;
	    end ;	! Bad first character.

	tes ;	! Dispatch on first character.

    true
    end ;	! GENPRI
global routine gennum(a_lexeme, a_description) =

!++
! Functional Description:
!
!	This routine checks that the given lexeme is a valid generation
!	number, and returns TRUE if it is.  The given description is
!	a phrase describing what the lexeme is supposed to be, for use
!	in error messages.
!
! Formal Parameters:
!
!	a_lexeme:	Address of a descriptor for the lexeme to be checked.
!			The lexeme must have non-zero length.
!	a_description:	Address of a descriptor for a phrase describing
!			the lexeme, for use in error messages.
!
! Implicit Inputs:
!
!	None
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE if the lexeme is valid, otherwise FALSE.
!
! Side Effects:
!
!	None
!
!--

    begin	! GENNUM
    bind
	lexeme = .a_lexeme : desc_block,
	description = .a_description : desc_block ;

    local
	need_level,		! TRUE means a digit is needed.
	p_this ;		! Character pointer to current character.

    ! Make sure the lexeme is non-empty.
    if .lexeme[desc_len] eql 0
    then
	bug(cat(('GENNUM was given an empty '), description)) ;

    ! Look for a level number at the start.
    need_level = true ;

    ! Check each character.
    p_this = .lexeme[desc_ptr] ;
    incr i from 1 to .lexeme[desc_len] do
	begin	! Check one character and advance.
	selectone ch$rchar(.p_this) of
	    set		! Check one character.

	    [%c'0' to %c'9']:
		need_level = false ;

	    [%c'A' to %c'Z']:
		begin		! Letter.
		if .need_level
		then
		    begin	! Bad variant letter.
		    ers(s_badvar,cat('In ', description,', the name ',lexeme,
			    ' has the variant letter "', (1, .p_this),
			    '" misplaced')) ;
		    return false ;
		    end ;	! Bad variant letter.
		need_level = true ;
		end ;		! Letter.

	    [otherwise]:
		begin		! Invalid character.
		errchr(.p_this, lexeme, description) ;
		return false ;
		end ;		! Invalid character.
	    tes ;	! Check one character.

	p_this = ch$plus(.p_this, 1) ;
	end ;	! Check one character and advance.

    ! Make sure the symbol ends in a level number.
    if .need_level
    then
	begin	! No final level.
	ers(s_nolevel,cat('In ',description,', the name ',lexeme,
		' must end with a level number')) ;
	return false ;
	end ;	! No final level.

    true
    end ;	! GENNUM
routine node_desc_init(a_node_desc, a_text, a_tree) : novalue =

!++
! Functional Description:
!
!	This routine initializes a component descriptor in a parse tree node
!	block. The descriptor becomes either a string descriptor or the
!	descriptor of another node block.
!
! Formal Parameters:
!
!	a_node_desc:	Address of a component descriptor, of which a node
!			block has four.  This descriptor will be initialized
!			to denote either the text given by the second
!			parameter, or the node block given by the third.
!	a_text:		Address of a descriptor of the text that the node
!			component descriptor is to denote.  This parameter is
!			used only if the third parameter is K_NULL.
!	a_tree:		Address of a node block that the node component
!			descriptor is to denote.  If this parameter is K_NULL,
!			the node component descriptor is set equal to the
!			text descriptor given by the second parameter.
!			Otherwise, the second parameter is ignored, and the
!			node component descriptor is set to denote the node
!			block given by the third parameter.
!
! Implicit Inputs:
!
!	None
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	None
!
! Side Effects:
!
!	None
!
!--

    begin	! NODE_DESC_INIT
    bind
	node_desc = .a_node_desc : desc_block,
	text = .a_text : desc_block,
	tree = .a_tree ;

    ! Initialize the descriptor.
    if tree eql k_null
    then
	$str_desc_init(descriptor = node_desc, string = text)
    else
	$xpo_desc_init(descriptor = node_desc,
		      binary_data = (k_nod_units, tree, units)) ;

    ! Make sure CMS conventions are consistent with XPORT's.
    if not (.node_desc[desc_typ] eql k_nod_desc_text
	 or .node_desc[desc_typ] eql k_nod_desc_node)
    then
	bug(lit('XPORT problem in NODE_DESC_INIT')) ;

    end ;	! NODE_DESC_INIT
global routine prevbl(a_user_string, syntax) =

!++
! Functional Description:
!
!	This routine checks that the character preceding the given string
!	in memory is a space or horizontal tab.
!
! Formal Parameters:
!
!	A_USER_STRING	Address of a descriptor of a string.  The character
!			just before this string in memory is to be examined.
!
!	SYNTAX		Integer code for the syntactic construct currently
!			being recognized.  This is used in error messages.
!
! Implicit Inputs:
!
!	None
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE means the string was preceded by a space or tab.  FALSE means
!	not, and the user has been informed of his mistake.
!
! Side Effects:
!
!	None
!
!--

    begin	! PREVBL
    bind
	user_string = .a_user_string : desc_block ;
    local
	p_previous ;		! To character before the user string.

    ! Check for comma lists (only allowed with k_ext_fname_syn )

    if  .syntax eql k_ext_fname_syn
	and ch$rchar(.user_string[desc_ptr]) eql %c','
    then
 	p_previous = .user_string[desc_ptr]
    else
 	p_previous = ch$plus(.user_string[desc_ptr], -1) ;

    if .syntax neq k_ext_fname_syn
    then
	begin
    	if ch$rchar(.p_previous) neq %c' ' and ch$rchar(.p_previous) neq 9
    	then
	    begin	! Non-blank.
	    ers(s_nospace,cat(codspl(.syntax), ' starting at ',
		(min(.user_string[desc_len], 15), .user_string[desc_ptr]),
		' must be preceded by a space or tab')) ;
 	    return false ;
	    end ;	! Non-blank.
	end
	else		! We can allow commas here 
	   begin
	   if (ch$rchar(.p_previous) neq %c' ' and ch$rchar(.p_previous) neq 9
	      and ch$rchar(.p_previous) neq %c',') 
    	    then
	    	begin	! Non-blank and  non-comma
	    	ers(s_nospace,cat(codspl(.syntax), ' starting at ',
		    (min(.user_string[desc_len], 15), .user_string[desc_ptr]),
		    ' must be preceded by a space or a tab or a comma')) ;
	    	return false ;
	    	end ;		! Non-blank and non-comma
	     end;


    true
    end ;	! PREVBL
global routine recpar(user_string, syntax, a_a_param) =

!++
! Functional Description:
!
!	This routine recognizes the next item in the user string as a
!	parameter of the given syntax.  It allocates a parameter block
!	and returns its address.
!
! Formal Parameters:
!
!	user_string:	Address of a descriptor for the user string, at the
!			beginning of which the parameter is to be recognized.
!			This descriptor will be advanced beyond the parameter
!			by calling NXTLEX.
!	syntax:		An integer code for the paramter syntax to be
!			recognized.  These codes are defined in COMUSR.REQ.
!	a_a_param:	Address of a fullword in which the routine will store
!			the address of a paramter block describing the
!			parameter recognized.
!
! Implicit Inputs:
!
!	None
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE if the user made no mistakes, otherwise FALSE.
!
! Side Effects:
!
!	A parameter block and other data structures are allocated
!	in COMZON using ZALLOC.
!
!--

    begin	! RECPAR

    map
	user_string : ref desc_block;

    bind
	r_param = .a_a_param : ref parameter_block ;

    ! If a parameter was supplied, make sure it is preceded by a space or tab.
    if .user_string[desc_len] gtr 0 
    then
	if not prevbl(.user_string, .syntax)
	then
	    return false ;

    ! Allocate and initialize the parameter block.
    r_param = zalloc(k_par_units, comzon) ;
    r_param[par_a_next] = k_null ;
    r_param[par_a_qual] = k_null ;
    r_param[par_a_tree] = k_null ;

    ! In this release, every parameter is a single lexeme, so get and check it.
    ! (see if we have to prompt for the parameter before calling nxtlex)
    if
	.user_string[desc_len] eql 0
    then
	!prompting is needed if there is no more text in the line
	begin

	local
	    new_stg : ref desc_block;

	do
	    begin
	    selectone .syntax of
		set

		[k_cls_name_syn]:
		    new_stg=ask(prompt_lit('Class'));

		[k_dir_spec_syn]:
		    new_stg=ask(prompt_lit('Directory'));

		[k_file_spec_syn,k_ext_fname_syn]:
		    new_stg=ask(prompt_lit('File'));

		[k_elem_ref_syn,k_wild_elem_ref_syn]:
		    new_stg=ask(prompt_lit('Element'));

		[otherwise]:
		    bug(cat('Bad parameter syntax code before processing ',
				.user_string));

		tes
	    end
	until
	    .new_stg[desc_len] neq 0;

	!Now add the new text to the line
	bldcom(.new_stg)
	end;

    if
	not nxtlex(.user_string,
			if .syntax eql k_file_spec_syn or
			   .syntax eql k_dir_spec_syn or
			   .syntax eql k_ext_fname_syn
			then k_file_spec_lex
			else k_normal_lex,
		  codspl(.syntax), r_param[par_text])
    then
	return false ;

    selectone .syntax of
	set	! Syntax.

	[k_cls_name_syn]:
	    clsnam(r_param[par_text], codspl(.syntax)) ;

	[k_dir_spec_syn, k_file_spec_syn]:
	    true ;	! No action is needed.

	[k_elem_ref_syn, k_ext_fname_syn]:
	    chk_name_type(r_param[par_text], codspl(.syntax)) ;

	[k_wild_elem_ref_syn]:
	    wild_element_ref(r_param[par_text], codspl(.syntax)) ;

	[otherwise]:
	    bug(cat('Bad parameter syntax code before processing ',
				.user_string)) ;

	tes	! Syntax.
    end ;	! RECPAR
routine wild_element_ref(a_lexeme, a_description) =

!++
! Functional Description:
!
!	This routine checks that a given lexeme is a valid element name
!	or a valid wild card construction for an element name.
!
! Formal Parameters:
!
!	A_LEXEME	Address of a descriptor of a lexeme to check.
!
!	A_DESCRIPTION	Address of a descriptor for a phrase describing
!			the lexeme, for use in error messages.
!
! Implicit Inputs:
!
!	None
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE means the user made no mistake.  FALSE means the user has been
!	informed of his mistake.
!
! Side Effects:
!
!	None
!
!--

    begin	! WILD_ELEMENT_REF
    bind
	lexeme = .a_lexeme : desc_block,
	description = .a_description : desc_block ;

    ! Only one form of wild card is allowed in this release.
    if $str_eql(string1 = lexeme, string2 = '*.*')
    then
	return true ;
    if not ch$fail(ch$find_ch(len_comma_ptr(lexeme), %c'*'))
    then
	begin	! Bad wild cards.
	ers(s_badwild,cat(lexeme, ' must be ', description)) ;
	return false ;
	end ;	! Bad wild cards.

    ! Check the non-wild element name.
    chk_name_type(lexeme, description)

    end ;	! WILD_ELEMENT_REF
end				! Module PARAMS
eludom