[comp.sources.misc] v19i031: dmake - dmake version 3.7, Part10/37

dvadura@watdragon.waterloo.edu (Dennis Vadura) (05/11/91)

Submitted-by: Dennis Vadura <dvadura@watdragon.waterloo.edu>
Posting-number: Volume 19, Issue 31
Archive-name: dmake/part10
Supersedes: dmake-3.6: Volume 15, Issue 52-77

---- Cut Here and feed the following to sh ----
#!/bin/sh
# this is dmake.shar.10 (part 10 of a multipart archive)
# do not concatenate these parts, unpack them in order with /bin/sh
# file dmake/getinp.c continued
#
if test ! -r _shar_seq_.tmp; then
	echo 'Please unpack part 1 first!'
	exit 1
fi
(read Scheck
 if test "$Scheck" != 10; then
	echo Please unpack part "$Scheck" next!
	exit 1
 else
	exit 0
 fi
) < _shar_seq_.tmp || exit 1
if test -f _shar_wnt_.tmp; then
sed 's/^X//' << 'SHAR_EOF' >> 'dmake/getinp.c' &&
X	            tok-- );
X	       tok[1] = '\0';
X	    }
X	    else
X	       lhs = NIL(char);
X
X	    op++;
X	    rhs = _strspn( op+1, " \t" );
X	    if( !*rhs ) rhs = NIL(char);
X
X	    if( (rhs == NIL(char)) || (lhs == NIL(char)) )
X	       result = (rhs == lhs) ? TRUE : FALSE;
X	    else {
X	       tok = rhs + strlen( rhs );
X	       for( tok=tok-1; (tok != lhs) && ((*tok == ' ')||(*tok == '\t'));
X		    tok--);
X	       tok[1] = '\0';
X
X	       result = (strcmp( lhs, rhs ) == 0) ? TRUE : FALSE;
X	    }
X
X	    if( *op == '!' ) result = !result;
X	 }
X
X	 if( expr != NIL(char) ) FREE( expr );
X
X	 if( opcode == ST_IF ) {
X	    Nest_level++;
X	    ifcntl[Nest_level] |= SEEN_IF;
X	 }
X
X	 if( result )
X	    action[ Nest_level ] = action[ Nest_level-1 ];
X	 else
X	    action[ Nest_level ] = 1;
X	 break;
X
X      case ST_ELSE:
X	 if( Nest_level <= 0 ) Fatal( ".ELSE without .IF" );
X	 if( ifcntl[Nest_level] & SEEN_ELSE )
X	    Fatal( "Missing .IF or .ELIF before .ELSE" );
X
X	 if( action[ Nest_level-1 ] != 1 )
X	    action[ Nest_level ] ^= 0x1;	/* flip between 0 and 1	*/
X	 ifcntl[Nest_level] |= SEEN_ELSE;
X	 break;
X
X      case ST_END:
X	 ifcntl[Nest_level] = SEEN_END;
X	 Nest_level--;
X	 if( Nest_level < 0 ) Fatal( "Unmatched .END" );
X	 break;
X   }
X
X   DB_RETURN( action[ Nest_level ] );
}
SHAR_EOF
chmod 0640 dmake/getinp.c ||
echo 'restore of dmake/getinp.c failed'
Wc_c="`wc -c < 'dmake/getinp.c'`"
test 13281 -eq "$Wc_c" ||
	echo 'dmake/getinp.c: original size 13281, current size' "$Wc_c"
rm -f _shar_wnt_.tmp
fi
# ============= dmake/hash.c ==============
if test -f 'dmake/hash.c' -a X"$1" != X"-c"; then
	echo 'x - skipping dmake/hash.c (File already exists)'
	rm -f _shar_wnt_.tmp
else
> _shar_wnt_.tmp
sed 's/^X//' << 'SHAR_EOF' > 'dmake/hash.c' &&
/* RCS      -- $Header: /u2/dvadura/src/generic/dmake/src/RCS/hash.c,v 1.1 91/05/06 15:23:15 dvadura Exp $
-- SYNOPSIS -- hashing function for hash tables.
-- 
-- DESCRIPTION
--      Hash an identifier.  The hashing function works by computing the sum
--      of each char and the previous hash value multiplied by 129.  Finally the
--      length of the identifier is added in.  This way the hash depends on the
--      chars as well as the length, and appears to be sufficiently unique,
--      and is FAST to COMPUTE, unlike the previous hash function...
-- 
-- AUTHOR
--      Dennis Vadura, dvadura@watdragon.uwaterloo.ca
--      CS DEPT, University of Waterloo, Waterloo, Ont., Canada
--
-- COPYRIGHT
--      Copyright (c) 1990 by Dennis Vadura.  All rights reserved.
-- 
--      This program is free software; you can redistribute it and/or
--      modify it under the terms of the GNU General Public License
--      (version 1), as published by the Free Software Foundation, and
--      found in the file 'LICENSE' included with this distribution.
-- 
--      This program is distributed in the hope that it will be useful,
--      but WITHOUT ANY WARRANTY; without even the implied warrant of
--      MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
--      GNU General Public License for more details.
-- 
--      You should have received a copy of the GNU General Public License
--      along with this program;  if not, write to the Free Software
--      Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
--
-- LOG
--     $Log:	hash.c,v $
X * Revision 1.1  91/05/06  15:23:15  dvadura
X * dmake Release Version 3.7
X * 
*/
X
#include "extern.h"
X
PUBLIC uint16
Hash( id, phv )/*
=================
X      This function computes the identifier's hash value and returns the hash
X      value modulo the key size as well as the full hash value.  The reason
X      for returning both is so that hash table searches can be sped up.  You
X      compare hash keys instead and compare strings only for those whose 32-bit
X      hash keys match. (not many) */
X
char   *id;
uint32 *phv;
{
X   register char   *p    = id;
X   register uint32 hash  = (uint32) 0;
X
X   while( *p ) hash = (hash << 7) + hash + (uint32) (*p++);
X   *phv = hash = hash + (uint32) (p-id);
X
X   return( (uint16) (hash % HASH_TABLE_SIZE) );
}
X
SHAR_EOF
chmod 0640 dmake/hash.c ||
echo 'restore of dmake/hash.c failed'
Wc_c="`wc -c < 'dmake/hash.c'`"
test 2324 -eq "$Wc_c" ||
	echo 'dmake/hash.c: original size 2324, current size' "$Wc_c"
rm -f _shar_wnt_.tmp
fi
# ============= dmake/imacs.c ==============
if test -f 'dmake/imacs.c' -a X"$1" != X"-c"; then
	echo 'x - skipping dmake/imacs.c (File already exists)'
	rm -f _shar_wnt_.tmp
else
> _shar_wnt_.tmp
sed 's/^X//' << 'SHAR_EOF' > 'dmake/imacs.c' &&
/* RCS      -- $Header: /u2/dvadura/src/generic/dmake/src/RCS/imacs.c,v 1.1 91/05/06 15:23:16 dvadura Exp $
-- SYNOPSIS -- define default internal macros.
-- 
-- DESCRIPTION
--	This file adds to the internal macro tables the set of default
--	internal macros, and for those that are accessible internally via
--	variables creates these variables, and initializes them to point
--	at the default values of these macros.
--
-- AUTHOR
--      Dennis Vadura, dvadura@watdragon.uwaterloo.ca
--      CS DEPT, University of Waterloo, Waterloo, Ont., Canada
--
-- COPYRIGHT
--      Copyright (c) 1990 by Dennis Vadura.  All rights reserved.
-- 
--      This program is free software; you can redistribute it and/or
--      modify it under the terms of the GNU General Public License
--      (version 1), as published by the Free Software Foundation, and
--      found in the file 'LICENSE' included with this distribution.
-- 
--      This program is distributed in the hope that it will be useful,
--      but WITHOUT ANY WARRANTY; without even the implied warrant of
--      MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
--      GNU General Public License for more details.
-- 
--      You should have received a copy of the GNU General Public License
--      along with this program;  if not, write to the Free Software
--      Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
--
-- LOG
--     $Log:	imacs.c,v $
X * Revision 1.1  91/05/06  15:23:16  dvadura
X * dmake Release Version 3.7
X * 
*/
X
#include "extern.h"
X
static	void	_set_int_var ANSI((char *, char *, int, int *));
static	void	_set_string_var ANSI((char *, char *, int, char **));
static	void	_set_bit_var ANSI((char *, char *, int));
X
/*
** Arrange to parse the strings stored in Rules[]
*/
PUBLIC void
Make_rules()
{
X   Parse(NIL(FILE));
}
X
X
#define M_FLAG   M_DEFAULT | M_EXPANDED
X
/*
** Add to the macro table all of the internal macro variables plus
** create secondary variables which will give access to their values
** easily, both when needed and when the macro value is modified.
** The latter is accomplished by providing a flag in the macro and a field
** which gives a pointer to the value if it is a char or string macro value
** and a mask representing the bit of the global flag register that is affected
** by this macro's value.
*/
PUBLIC void
Create_macro_vars()
{
X   static char* switchar;
X   char   swchar[2];
X
X   swchar[0] = Get_switch_char(), swchar[1] = '\0';
X   _set_string_var("SWITCHAR", swchar, M_PRECIOUS, &switchar);
X   _set_string_var("DIRSEPSTR", "/", M_PRECIOUS, &DirSepStr);
X   _set_string_var("DIRBRKSTR", DirBrkStr, M_PRECIOUS, &DirBrkStr);
X
X   _set_bit_var(".SILENT",   "", A_SILENT  );
X   _set_bit_var(".IGNORE",   "", A_IGNORE  );
X   _set_bit_var(".PRECIOUS", "", A_PRECIOUS);
X   _set_bit_var(".EPILOG",   "", A_EPILOG  );
X   _set_bit_var(".PROLOG",   "", A_PROLOG  );
X   _set_bit_var(".NOINFER",  "", A_NOINFER );
X   _set_bit_var(".SEQUENTIAL","",A_SEQ     );
X   _set_bit_var(".USESHELL", "", A_SHELL   );
X   _set_bit_var(".SWAP",     "", A_SWAP    );
X   _set_bit_var(".MKSARGS",  "", A_MKSARGS );
X
X   Glob_attr = A_DEFAULT;        /* set all flags to NULL   */
X
X   _set_string_var("SHELL",        "",  M_DEFAULT, &Shell       );
X   _set_string_var("SHELLFLAGS",   " ", M_DEFAULT, &Shell_flags );
X   _set_string_var("GROUPSHELL",   "",  M_DEFAULT, &GShell      );
X   _set_string_var("GROUPFLAGS",   " ", M_DEFAULT, &GShell_flags);
X   _set_string_var("SHELLMETAS",   "",  M_DEFAULT, &Shell_metas );
X   _set_string_var("GROUPSUFFIX",  "",  M_DEFAULT, &Grp_suff    );
X   _set_string_var("PREP",         "0", M_DEFAULT, &Prep        );
X   _set_string_var("AUGMAKE",NIL(char), M_DEFAULT, &Augmake     );
X   _set_string_var(".SETDIR",      "",  M_DEFAULT, &Start_dir   );
X   _set_string_var(".KEEP_STATE",  "",  M_DEFAULT, &Keep_state  );
X
X   _set_string_var("MAKEDIR", Get_current_dir(), M_PRECIOUS|M_NOEXPORT,
X         &Makedir);
X   _set_string_var("PWD",  Makedir,  M_DEFAULT|M_NOEXPORT, &Pwd);
X   _set_string_var("TMD",  "",       M_DEFAULT|M_NOEXPORT, &Tmd);
X
X   Def_macro("NULL", "", M_PRECIOUS|M_NOEXPORT|M_FLAG);
X 
X   _set_int_var( "MAXLINELENGTH", "0", M_DEFAULT|M_NOEXPORT, &Buffer_size );
X   (void) Def_macro("MAXLINELENGTH", "0", M_FLAG | M_DEFAULT);
X
X   /* set MAXPROCESSLIMIT high initially so that it allows MAXPROCESS to
X    * change from command line. */
X   _set_int_var( "MAXPROCESSLIMIT", "100", M_DEFAULT|M_NOEXPORT, &Max_proclmt );
X   _set_int_var( "MAXPROCESS", "1", M_DEFAULT|M_NOEXPORT, &Max_proc );
}
X
X
/*
** Define an integer variable value, and set up the macro.
*/
static void
_set_int_var(name, val, flag, var)
char *name;
char *val;
int  flag;
int  *var;
{
X   HASHPTR hp;
X
X   hp = Def_macro(name, val, M_FLAG | flag);
X   hp->ht_flag |= M_VAR_INT | M_MULTI;
X   hp->MV_IVAR  = var;
X   *var         = atoi(val);
}
X
X
/*
** Define a string variables value, and set up the macro.
*/
static void
_set_string_var(name, val, flag, var)
char *name;
char *val;
int  flag;
char **var;
{
X   HASHPTR hp;
X
X   hp = Def_macro(name, val, M_FLAG | flag);
X   hp->ht_flag |= M_VAR_STRING | M_MULTI;
X   hp->MV_SVAR  = var;
X   *var         = hp->ht_value;
}
X
X
/*
** Define a bit variable value, and set up the macro.
*/
static void
_set_bit_var(name, val, mask)
char *name;
char *val;
int  mask;
{
X   HASHPTR hp;
X
X   hp           = Def_macro(name, val, M_FLAG);
X   hp->ht_flag |= M_VAR_BIT | M_MULTI;
X   hp->MV_MASK  = mask;
X   hp->MV_BVAR  = &Glob_attr;
}
SHAR_EOF
chmod 0640 dmake/imacs.c ||
echo 'restore of dmake/imacs.c failed'
Wc_c="`wc -c < 'dmake/imacs.c'`"
test 5479 -eq "$Wc_c" ||
	echo 'dmake/imacs.c: original size 5479, current size' "$Wc_c"
rm -f _shar_wnt_.tmp
fi
# ============= dmake/infer.c ==============
if test -f 'dmake/infer.c' -a X"$1" != X"-c"; then
	echo 'x - skipping dmake/infer.c (File already exists)'
	rm -f _shar_wnt_.tmp
else
> _shar_wnt_.tmp
sed 's/^X//' << 'SHAR_EOF' > 'dmake/infer.c' &&
/* RCS      -- $Header: /u2/dvadura/src/generic/dmake/src/RCS/infer.c,v 1.1 91/05/06 15:23:17 dvadura Exp $
-- SYNOPSIS -- infer how to make a target.
-- 
-- DESCRIPTION
--	This file contains the code to infer a recipe, and possibly some new
--	prerequisites for a target which dmake does not know how to make, or
--	has no explicit recipe.
--
--	The inference fails if no path through the inference graph can be
--	found by which we can make the target.
-- 
-- AUTHOR
--      Dennis Vadura, dvadura@watdragon.uwaterloo.ca
--      CS DEPT, University of Waterloo, Waterloo, Ont., Canada
--
-- COPYRIGHT
--      Copyright (c) 1990 by Dennis Vadura.  All rights reserved.
-- 
--      This program is free software; you can redistribute it and/or
--      modify it under the terms of the GNU General Public License
--      (version 1), as published by the Free Software Foundation, and
--      found in the file 'LICENSE' included with this distribution.
-- 
--      This program is distributed in the hope that it will be useful,
--      but WITHOUT ANY WARRANTY; without even the implied warrant of
--      MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
--      GNU General Public License for more details.
-- 
--      You should have received a copy of the GNU General Public License
--      along with this program;  if not, write to the Free Software
--      Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
--
-- LOG
--     $Log:	infer.c,v $
X * Revision 1.1  91/05/06  15:23:17  dvadura
X * dmake Release Version 3.7
X * 
*/
X
#include "extern.h"
X
/* attributes that get transfered from the % start cell to the inferred
X * cells. */
X
#define A_TRANSFER  (A_EPILOG | A_PRECIOUS | A_SILENT | A_SHELL | A_SETDIR |\
X		     A_SEQ | A_LIBRARY | A_IGNORE | A_PROLOG | A_SWAP |\
X		     A_NOSTATE )
X
X
/* Define local static functions */
static DFALINKPTR _dfa_subset  ANSI((DFALINKPTR, DFASETPTR));
static void 	  _free_dfas   ANSI((DFALINKPTR));
static int	  _count_dots  ANSI((char *));
static char *	  _build_name  ANSI((char *, char *, char *));
static void	  _free_icells ANSI(());
static ICELLPTR   _union_iset  ANSI((ICELLPTR, ICELLPTR));
static ICELLPTR   _add_iset    ANSI((ICELLPTR,ICELLPTR,CELLPTR,DFALINKPTR,
X				     CELLPTR,int,int,char *,char *, int));
static ICELLPTR   _derive_prerequisites ANSI((ICELLPTR, ICELLPTR *));
static char *	  _dump_inf_chain ANSI((ICELLPTR, int, int));
X
static int _prep = -1;	/* Integer value of Prep variable */
X
X
PUBLIC void
Infer_recipe( cp, setdirroot )/*
================================
X   Perform a breadth-first search of the inference graph and return if
X   possible an inferred set of prerequisites for making the current target.
*/
CELLPTR cp;
CELLPTR setdirroot;
{
X   ICELLPTR nomatch, match;
X
X   DB_ENTER("Infer_recipe");
X
X   if( cp->ce_attr & A_NOINFER ) {DB_VOID_RETURN;}
X   if( _prep == -1 ) _prep = atoi(Prep);  /* _dfa_subset needs _prep */
X
X   match = NIL(ICELL);
X   nomatch = _add_iset( NIL(ICELL), NIL(ICELL), NIL(CELL), NIL(DFALINK),
X			setdirroot, _prep+_count_dots(cp->CE_NAME), 0,
X			_strdup(cp->CE_NAME), NIL(char),
X			cp->ce_time != (time_t)0L);
X
X   /* Make sure we try whole heartedly to infer at least one suffix */
X   if( nomatch->ic_dmax == 0 ) ++nomatch->ic_dmax;
X
X   DB_EXECUTE( "inf", _dump_iset("nomatch",nomatch); );
X
X   while( nomatch != NIL(ICELL) ) {
X      ICELLPTR new_nomatch = NIL(ICELL);
X      ICELLPTR ic, pmatch, mmatch;
X      CELLPTR  prereq;
X      int      first;
X
X      for( ic=nomatch; ic != NIL(ICELL); ic=ic->ic_next ) {
X	 int ipush = FALSE;
X
X	 if( ic->ic_dir ) ipush = Push_dir(ic->ic_dir, ic->ic_name, FALSE);
X	 match = _union_iset(match, _derive_prerequisites(ic, &new_nomatch));
X	 if( ipush ) Pop_dir(FALSE);
X      }
X
X      DB_EXECUTE( "inf", _dump_iset("match",match); );
X      DB_EXECUTE( "inf", _dump_iset("nomatch",new_nomatch); );
X
X      /* We have now deduced the two sets MATCH and NOMATCH.  MATCH holds the
X       * set of edges that we encountered that matched.  If this set is empty
X       * then we can apply transitive closure (if enabled) to the elements of
X       * NOMATCH to see if we can find some other method to make the target.
X       *
X       * If MATCH is non-empty, we have found a method for making the target.
X       * It is the shortest method for doing so (ie. uses fewest number of
X       * steps).  If MATCH contains more than one element then we have a
X       * possible ambiguity.
X       */
X      if( match == NIL(ICELL) ) {
X	 nomatch = new_nomatch;
X	 continue;
X      }
X
X      /* Ok, we have a set of possible matches in MATCH, we should check the
X       * set for ambiguity.  If more than one inference path exists of the
X       * same depth, then we may issue an ambigous inference error message.
X       *
X       * The message is suppressed if MATCH contains two elements and one of
X       * them is the empty-prerequisite-rule.  In this case we ignore the
X       * ambiguity and take the rule that infers the prerequisite.
X       *
X       * Also if there are any chains that rely on a non-existant prerequisite
X       * that may get made because it has a recipe then we prefer any that
X       * rely on existing final prerequisites over those that we have to make.
X       *
X       * NOTE:  May turn this around at some point.
X       */
X
X      /* Split out those that have to be made from those that end in
X       * prerequisites that already exist. */
X      pmatch = mmatch = NIL(ICELL);
X      for(; match; match = ic ) {
X	 ic = match->ic_next;
X	 match->ic_next = NIL(ICELL);
X
X	 if( match->ic_exists )
X	    pmatch = _union_iset(pmatch, match);
X	 else
X	    mmatch = _union_iset(mmatch, match);
X      }
X
X      if( pmatch )
X	 match = pmatch;
X      else
X	 match = mmatch;
X
X      /* Make sure it is unique */
X      if( match->ic_next != NIL(ICELL) ) {
X	 int dump = (match->ic_next->ic_next != NIL(ICELL));
X
X	 /* Check for definite ambiguity */
X	 if( !dump )
X	    if( (match->ic_meta->ce_prq && match->ic_next->ic_meta->ce_prq) ||
X	        (!match->ic_meta->ce_prq && !match->ic_next->ic_meta->ce_prq)  )
X	       dump = TRUE;
X	    else if(!match->ic_meta->ce_prq && match->ic_next->ic_meta->ce_prq )
X	       match = match->ic_next;
X
X	 if( dump ) {
X	    int count = 1;
X
X	    Continue = TRUE;
X	    Error( "Ambiguous inference chains for target '%s'", cp->CE_NAME );
X	    for( ic=match; ic; ic=ic->ic_next )
X	       (void) _dump_inf_chain(ic, TRUE, count++);
X	    Fatal( "resolve ambiguity before proceeding.");
X	    /*NOTREACHED*/
X	 }
X      }
X
X      /* MATCH now points at the derived recipe.  We must now take cp, and
X       * construct the correct graph so that the make may proceed. */
X
X      if( Verbose & V_INFER ) {
X	 char *tmp = _dump_inf_chain(match, TRUE, FALSE);
X	 printf("%s:  Inferring prerequistes and recipes using:\n%s:  ... %s\n",
X		 Pname, Pname, tmp );
X	 FREE(tmp);
X      }
X
X      pmatch = NIL(ICELL);
X      prereq = NIL(CELL);
X      first  = TRUE;
X
X      while( match ) {
X         CELLPTR infcell=NIL(CELL);
X
X	 /* Compute the inferred prerequisite first. */
X	 if( match->ic_meta && match->ic_name ) {
X	    infcell = Def_cell( match->ic_name );
X
X	    if( first )
X	       infcell->ce_flag |= F_RULES;
X	    else
X	       infcell->ce_flag |= F_INFER|F_REMOVE|F_TARGET;
X
X	    if( !match->ic_flag )
X	       infcell->ce_attr |= A_NOINFER;
X	 }
X
X	 /* Now attach the recipe from the previous MATCH entry and then
X	  * add any prerequisites that you might think are required. */
X	 if( infcell == NIL(CELL) && match->ic_name )
X	    infcell = cp;
X
X	 /* Add global prerequisites from previous rule if there are any and
X	  * the recipe. */
X	 if( pmatch ) {
X	    CELLPTR imeta = pmatch->ic_meta;
X	    LINKPTR lp;
X
X	    infcell->ce_per   = pmatch->ic_dfa->dl_per;
X	    infcell->ce_attr |= (imeta->ce_attr & A_TRANSFER);
X
X	    if( !(infcell->ce_flag & F_RULES) ) {
X	       infcell->ce_flag   |= (imeta->ce_flag & (F_SINGLE|F_GROUP));
X	       infcell->ce_recipe  = imeta->ce_recipe;
X	    }
X
X	    pmatch->ic_dfa->dl_per = NIL(char);
X
X	    /* If infcell already had a directory set then modify it based on
X	     * whether it was the original cell or some intermediary. */
X	    if( imeta->ce_dir )
X	       if( infcell->ce_dir && infcell == cp ) {
X		  /* cp->ce_dir was set and we have pushed the directory prior
X		   * to calling this routine.  We should therefore pop it and
X		   * push the new concatenated directory required by the
X		   * inference. */
X		  infcell->ce_dir=_strdup(Build_path(infcell->ce_dir,
X						     imeta->ce_dir));
X	       }
X	       else
X		  infcell->ce_dir = imeta->ce_dir;
X
X	    for( lp=imeta->ce_indprq; lp != NIL(LINK); lp=lp->cl_next ) {
X	       char    *name = lp->cl_prq->CE_NAME;
X	       CELLPTR tcp;
X
X	       name = _build_name( cp->CE_NAME, name, infcell->ce_per );
X	       tcp  = Def_cell( name );
X	       tcp->ce_flag |= F_REMOVE;
X	       Add_prerequisite( infcell, tcp, FALSE, FALSE );
X
X	       if( Verbose & V_INFER )
X		  printf( "%s:  Inferred indirect prerequisite [%s]\n",
X			  Pname, name );
X	       FREE(name);
X	    }
X	 }
X
X	 /* Add the previous cell as the prerequisite */
X	 if( prereq )
X	    (Add_prerequisite(infcell,prereq,FALSE,FALSE))->cl_flag |= F_TARGET;
X
X	 pmatch = match;
X	 prereq = infcell;
X	 match  = match->ic_parent;
X	 first  = FALSE;
X      }
X
X      DB_PRINT("inf", ("Terminated due to a match"));
X      break;
X   }
X
X   _free_icells();
X
X   DB_VOID_RETURN;
}
X
X
static ICELLPTR
_derive_prerequisites( ic, nnmp )/*
===================================
X   Take a cell and derive a set of prerequisites from the cell.  Categorize
X   them into those that MATCH (ie. those that we found in the file system),
X   and those that do not match NOMATCH that we may possibly have a look at
X   later.  When we process the next level of the breadth-first search.
X   
X   Once MATCH is non-empty we will stop inserting elements into NOMATCH
X   since we know that either MATCH is successful and unique or it will
X   issue an ambiguity error.  We will never go on to look at elements
X   in NOMATCH after wards. */
ICELLPTR ic;
ICELLPTR *nnmp;
{
X   ICELLPTR   match = NIL(ICELL);
X   DFALINKPTR pdfa;
X   DFALINKPTR dfas;
X
X   DB_ENTER("_derive_prerequisites");
X
X   /* If none of the inference nodes match then forget about the inference.
X    * The user did not tell us how to make such a target.  We also stop the
X    * Inference if the new set of DFA's is a proper subset of a previous
X    * subset and it's PREP counts exceed the value of Prep.
X    */
X   dfas = _dfa_subset( Match_dfa(ic->ic_name), &ic->ic_dfastack );
X
X   DB_EXECUTE("inf", _dump_dfa_stack(dfas, &ic->ic_dfastack); );
X
X   /* Ok, we have nothing here to work with so return an empty cell. */
X   if( dfas == NIL(DFALINK) ) {
X      DB_PRINT( "mem", ("%s:<- mem %ld",ic->ic_name, (long)coreleft()));
X      DB_PRINT( "inf", ("<<< Exit, no dfas, cp = %04x", NIL(CELL)) );
X      DB_RETURN( NIL(ICELL) );
X   }
X
X   /* Save the dfas, we are going to use on the stack for this cell. */
X   ic->ic_dfastack.df_set = dfas;
X
X   /* Run through the %-meta cells, build the prerequisite cells.  For each
X    * %-meta go through it's list of edges and try to use each in turn to
X    * decuce a likely prerequisite.  We perform a breadth-first search
X    * matching the first path that results in a unique method for making the
X    * target. */
X   for( pdfa = dfas; pdfa != NIL(DFALINK); pdfa = pdfa->dl_next ) {
X      LINK tl;
X      LINKPTR edge;
X      CELLPTR pmeta;
X
X      pmeta = pdfa->dl_meta;
X      DB_PRINT( "inf", ("Using dfa:  [%s]", pmeta->CE_NAME) );
X
X      /* If the %-meta is a singleton meta then deal with it differently from
X       * the case when it is a bunch of %-meta's found on the original entries
X       * prerequisite list. */
X      if( pmeta->ce_flag & F_MULTI )
X	 edge = pmeta->ce_prq;
X      else {
X	 tl.cl_prq = pmeta;
X	 tl.cl_next = NIL(LINK);
X	 edge = &tl;
X      }
X
X      /* Now run through the list of prerequisite edge's for the %-meta. */
X      for( ; edge != NIL(LINK); edge = edge->cl_next ) {
X	 HASHPTR  thp;		/* temporary hash table pointer		*/
X	 HASH     iprqh;	/* hash cell for new prerequisite	*/
X	 CELL     iprq;		/* inferred prerequisite to look for	*/
X	 CELLPTR  idirroot;	/* Inferred prerequisite root		*/
X	 CELLPTR  nidirroot;	/* Inferred prerequisite root		*/
X	 STRINGPTR ircp;	/* Inferred prerequisites recipe	*/
X	 char     *idir;	/* directory to CD to.			*/
X	 int      ipush = 0;	/* flag for push on inferred prereq     */
X	 char     *name = NIL(char); 		/* prerequisite name    */
X	 CELLPTR  meta = edge->cl_prq;
X	 int	  dmax_fix;
X	 int      trans;
X	 int      noinf;
X	 int	  exists;
X	 
X	 if( meta->ce_prq ) name = meta->ce_prq->cl_prq->CE_NAME;
X
X	 DB_PRINT( "inf", ("Trying edge from [%s] to [%s] for [%s]",
X		   meta->CE_NAME, name?name:"(nil)", ic->ic_name) );
X
X	 /* Set the temp CELL used for building prerequisite candidates to
X	  * all zero so that we don't have to keep initializing all the
X	  * fields. */
X	 {
X	    register char *s = (char *) &iprq;
X	    register int   n = sizeof(CELL);
X	    while( n ) { *s++ = '\0'; n--; }
X	 }
X
X	 nidirroot = idirroot = ic->ic_setdirroot;
X	 iprq.ce_name = &iprqh;
X
X	 if( name ) {
X	    /* Build the prerequisite name from the %-meta prerequisite given
X	     * for the %-meta rule. */
X	    iprqh.ht_name = _build_name( ic->ic_name, name, pdfa->dl_per );
X	    if((dmax_fix = (_count_dots(name)-_count_dots(meta->CE_NAME))) < 0)
X	       dmax_fix = 0;
X
X	    if( !strcmp(ic->ic_name, iprqh.ht_name) ||
X		(_count_dots(iprqh.ht_name) > ic->ic_dmax + dmax_fix) ) {
X	       FREE( iprqh.ht_name );
X	       continue;
X	    }
X
X	    DB_PRINT( "inf", ("Checking prerequisite [%s]", iprqh.ht_name) );
X
X	    /* See if the prerequisite CELL has been previously defined.  If
X	     * it has, then make a copy of it into iprq, and use it to try
X	     * the inference.  We make the copy so that we don't modify the
X	     * stat of the inferred cell if the inference fails.
X	     */
X	    thp = Get_name( iprqh.ht_name, Defs, FALSE );
X	    if(thp != NIL(HASH)) {
X	       iprq = *thp->CP_OWNR;
X	       ircp = iprq.ce_recipe;
X	    }
X	    else
X	       ircp = NIL(STRING);
X	 }
X	 else
X	    iprqh.ht_name = NIL(char);
X
X
X	 /* If the %-meta has a .SETDIR set then we change to the new
X	  * directory prior to performing the stat of the new prerequisite.
X	  * If the change of directory fails then the rule is droped from
X	  * further consideration.
X	  */
X	 if( iprq.ce_dir ) {
X	    if( ipush = Push_dir(iprq.ce_dir, iprqh.ht_name, TRUE) ) {
X	       nidirroot = thp->CP_OWNR;
X	       idir      = Pwd;
X	    }
X	    else {
X	       if( iprqh.ht_name ) FREE( iprqh.ht_name );
X	       continue;
X	    }
X	 }
X	 else
X	    idir = NIL(char);
X
X
X	 /* Stat the inferred prerequisite.
X	  */
X	 if( name ) {
X	    if( Verbose & V_INFER )
X	       printf( "%s:  Trying prerequisite [%s] for [%s]\n", Pname,
X		       iprqh.ht_name, ic->ic_name );
X
X	    if( !(iprq.ce_flag & F_STAT) ) Stat_target(&iprq, FALSE);
X	 }
X
X
X	 /* If the STAT succeeded or if the prerequisite has a recipe for
X	  * making it then it's a match and a candidate for getting infered.
X	  * Otherwise it is not a match, and we cannot yet tell if it is
X	  * going to be a successful path to follow, so we save it for
X	  * later consideration.
X	  */
X	 noinf = ((Glob_attr)&A_NOINFER);
X	 if( meta->ce_prq )
X	    noinf |= ((meta->ce_prq->cl_prq->ce_attr)&A_NOINFER);
X	 trans = Transitive || !noinf;
X	 exists = (iprq.ce_time != (time_t)0L);
X
X	 if( exists || (ircp != NIL(STRING)) || !name ) {
X	    match = _add_iset( match, ic, meta, pdfa, idirroot, ic->ic_dmax,
X			       trans, iprq.ce_name->ht_name, idir, exists );
X	    DB_PRINT("inf",("Added to MATCH %s",iprq.ce_name->ht_name));
X	 }
X	 else if( !noinf && match == NIL(ICELL) ) {
X	    *nnmp = _add_iset( *nnmp, ic, meta, pdfa, nidirroot, ic->ic_dmax,
X			       trans, iprq.ce_name->ht_name, idir, exists );
X	    DB_PRINT("inf",("Added to NOMATCH %s",iprq.ce_name->ht_name));
X	 }
X
X	 /* If we pushed a directory for the inferred prerequisite then
X	  * pop it.
X	  */
X	 if( ipush ) Pop_dir(FALSE);
X	 if( iprqh.ht_name ) FREE(iprqh.ht_name);
X      }
X   }
X
X   DB_RETURN(match);
}
X
X
static char *
_build_name( tg, meta, per )
char *tg;
char *meta;
char *per;
{
X   char    *name;
X
X   name = Apply_edit( meta, "%", per, FALSE, FALSE );
X   if( strchr(name, '$') ) {
X      HASHPTR m_at;
X      char *tmp;
X
X      m_at = Def_macro( "@", tg, M_MULTI );
X      tmp = Expand( name );
X
X      if( m_at->ht_value != NIL(char) ) {
X	 FREE( m_at->ht_value );
X	 m_at->ht_value = NIL(char);
X      }
X
X      if( name != meta ) FREE( name );
X      name = tmp;
X   }
X   else if( name == meta )
X      name = _strdup( name );
X
X   return(name);
}
X
X
static DFALINKPTR
_dfa_subset( pdfa, stack )/*
============================
X   This is the valid DFA subset computation.  Whenever a CELL has a Match_dfa
X   subset computed this algorithm is run to see if any of the previously
X   computed sets on the DFA stack are proper subsets of the new set.  If they
X   are, then any elements of the matching subset whose Prep counts exceed
X   the allowed maximum given by Prep are removed from the computed DFA set,
X   and hence from consideration, thereby cutting off the cycle in the
X   inference graph. */
DFALINKPTR	   pdfa;
register DFASETPTR stack;
{
X   register DFALINKPTR element;
X   DFALINKPTR          nelement;
X
X   DB_ENTER( "_dfa_subset" );
X
X   for(; pdfa != NIL(DFALINK) && stack != NIL(DFASET); stack = stack->df_next) {
X      int subset = TRUE;
X
X      for( element=stack->df_set; subset && element != NIL(DFALINK);
X           element=element->dl_next ) {
X         register DFALINKPTR subel;
X
X	 for( subel = pdfa;
X	      subel != NIL(DFALINK) && (subel->dl_meta != element->dl_meta);
X	      subel = subel->dl_next );
X
X	 if( subset = (subel != NIL(DFALINK)) ) element->dl_member = subel;
X      }
X
X      if( subset )
X	 for( element=stack->df_set; element != NIL(DFALINK);
X	      element=element->dl_next ) {
X	    DFALINKPTR mem = element->dl_member;
X	    int        npr = element->dl_prep + 1;
X
X	    if( npr > _prep )
X	       mem->dl_delete++;
X	    else
X	       mem->dl_prep = npr;
X	 }
X   }
X
X   for( element = pdfa; element != NIL(DFALINK); element = nelement ) {
X      nelement = element->dl_next;
X
X      if( element->dl_delete ) {
X	 /* A member of the subset has a PREP count equal to PREP, so
X	  * it should not be considered further in the inference, hence
X	  * we remove it from the doubly linked set list */
X	 if( element == pdfa )
X	    pdfa = element->dl_next;
X	 else
X	    element->dl_prev->dl_next = element->dl_next;
X
X	 if( element->dl_next != NIL(DFALINK) )
X	    element->dl_next->dl_prev = element->dl_prev;
X
X	 DB_PRINT("inf", ("deleting dfa [%s]", element->dl_meta->CE_NAME));
X	 FREE( element->dl_per );
X	 FREE( element );
X      }
X   }
X
X   DB_RETURN( pdfa );
}
X
X
X
static void
_free_dfas( chain )/*
=====================
X   Free the list of DFA's constructed by Match_dfa, and linked together by
X   LINK cells.  FREE the % value as well, as long as it isn't NIL. */
DFALINKPTR chain;
{
X   register DFALINKPTR tl;
X
X   DB_ENTER( "_free_dfas" );
X
X   for( tl=chain; tl != NIL(DFALINK); chain = tl ) {
X      tl = tl->dl_next;
X
X      DB_PRINT( "inf", ("Freeing DFA [%s], %% = [%s]", chain->dl_meta->CE_NAME,
X                chain->dl_per) );
X
X      if( chain->dl_per != NIL(char) ) FREE( chain->dl_per );
X      FREE( chain );
X   }
X
X   DB_VOID_RETURN;
}
X
X
static int
_count_dots( name )/*
=====================*/
char *name;
{
X   register char *p;
X   register int  i = 0;
X
X   for( p = name; *p; p++ ) if(*p == '.') i++;
X
X   return( i );
}
X
X
static ICELLPTR _icells = NIL(ICELL);
#ifdef DBUG
static int _icell_cost = 0;
#endif
X
static ICELLPTR
_add_iset( iset, parent, meta, dfa, setdirroot, dmax, noinf, name, dir, exists)
ICELLPTR   iset;
ICELLPTR   parent;
CELLPTR    meta;
DFALINKPTR dfa;
CELLPTR    setdirroot;
int	   dmax;
int	   noinf;
char	  *name;
char	  *dir;
int	   exists;
{
X   ICELLPTR icell;
X
X   DB_ENTER("_add_iset");
X   TALLOC(icell, 1, ICELL);
X
X   DB_EXECUTE("inf", _icell_cost+=(sizeof(ICELL)+strlen(dir)+strlen(name)+2););
X
X   icell->ic_meta = meta;
X   icell->ic_dfa  = dfa;
X   icell->ic_setdirroot = setdirroot;
X
X   if( parent ) icell->ic_dfastack.df_next = &parent->ic_dfastack;
X
X   icell->ic_dmax = dmax;
X   icell->ic_dir = _strdup(dir);
X   icell->ic_name = _strdup(name);
X   icell->ic_parent = parent;
X   icell->ic_next = iset;
X   icell->ic_flag = noinf;
X   icell->ic_exists = exists;
X
X   icell->ic_link = _icells;
X   _icells = icell;
X
X   DB_RETURN(icell);
}
X
X
static void
_free_icells()
{
X   register ICELLPTR ic;
X
X   DB_ENTER("_free_icells");
X
X   for( ; _icells; _icells = ic ) {
X      ic = _icells->ic_link;
X
X      _free_dfas(_icells->ic_dfastack.df_set);
X      if( _icells->ic_dir ) FREE(_icells->ic_dir);
X      if( _icells->ic_name) FREE(_icells->ic_name);
X      FREE(_icells);
X   }
X
X   DB_PRINT("inf",("Used %d memory for icells",_icell_cost));
X   DB_EXECUTE("inf", _icell_cost=0; );
X
X   DB_VOID_RETURN;
}
X
X
static ICELLPTR
_union_iset( iset, uset )
ICELLPTR iset;
ICELLPTR uset;
{
X   register ICELLPTR ic;
X
X   if( iset == NIL(ICELL) ) return(uset);
X
X   for( ic=iset; ic->ic_next != NIL(ICELL); ic=ic->ic_next );
X   ic->ic_next = uset;
X
X   return(iset);
}
X
X
static char *
_dump_inf_chain( ip, flag, print )/*
====================================*/
ICELLPTR ip;
int      flag;
int	 print;
{
X   char *tmp;
X
X   if( ip == NIL(ICELL) ) return(NIL(char));
X
X   tmp = _dump_inf_chain(ip->ic_parent, FALSE, FALSE);
X
X   if( ip->ic_meta ) {
X      tmp = _strjoin(tmp, "(", -1, TRUE);
X      tmp = _strjoin(tmp, ip->ic_meta->CE_NAME, -1, TRUE);
X
X      if( ip->ic_dir && !*ip->ic_dir ) {
X	 tmp = _strjoin(tmp, "[", -1, TRUE);
X	 if( strncmp(Makedir,ip->ic_dir, strlen(Makedir)) )
X	    tmp = _strjoin(tmp, ip->ic_dir, -1, TRUE);
X	 else
X	    tmp = _strjoin(tmp, ip->ic_dir+strlen(Makedir)+1, -1, TRUE);
X	 tmp = _strjoin(tmp, "]", -1, TRUE);
X      }
X      tmp = _strjoin(tmp, (ip->ic_name)?") -->":")", -1, TRUE);
X   }
X   
X   if( ip->ic_name ) tmp = _strapp( tmp, ip->ic_name );
X
X   if( flag && ip->ic_meta->ce_prq) {
X      tmp = _strjoin(tmp, "(", -1, TRUE);
X      tmp = _strjoin(tmp, ip->ic_meta->ce_prq->cl_prq->CE_NAME, -1, TRUE);
X      tmp = _strjoin(tmp, ")", -1, TRUE);
X   }
X
X   if( print ) {
X      fprintf( stderr, "%s:  %2d. %s\n", Pname, print, tmp );
X      FREE(tmp);
X      tmp = NIL(char);
X   }
X
X   return(tmp);
}
X
X
#ifdef DBUG
_dump_dfa_stack(dfas, dfa_stack)
DFALINKPTR dfas;
DFASETPTR  dfa_stack;
{
X   register DFALINKPTR pdfa;
X   char      *tmp = NIL(char);
X   DFASETPTR ds;
X
X   for( pdfa = dfas; pdfa != NIL(DFALINK); pdfa = pdfa->dl_next )
X      tmp = _strapp( tmp, pdfa->dl_meta->CE_NAME );
X
X   tmp = _strapp( tmp, ":: {" );
X   for( ds = dfa_stack; ds != NIL(DFASET); ds = ds->df_next ) {
X      tmp = _strapp( tmp, "[" );
X      for( pdfa = ds->df_set; pdfa != NIL(DFALINK); pdfa = pdfa->dl_next )
X	 tmp = _strapp( tmp, pdfa->dl_meta->CE_NAME );
X      tmp = _strapp( tmp, "]" );
X   }
X   tmp = _strapp( tmp, "}" );
X
X   printf( "DFA set and stack contents:\n%s\n", tmp );
X   FREE(tmp);
}
X
X
_dump_iset( name, iset )
char     *name;
ICELLPTR iset;
{
X   int cell = 0;
X
X   printf( "**** ISET for %s\n", name );
X   for( ; iset != NIL(ICELL); iset = iset->ic_next ){
X      printf( "cell %d\n", cell++ );
X      if( iset->ic_meta )
X	 printf( "edge: %s --> %s\n", iset->ic_meta->CE_NAME,
X		 iset->ic_meta->ce_prq ?
X		 iset->ic_meta->ce_prq->cl_prq->CE_NAME :
X		 "(nil)" );
X      else
X	 printf( "edge: (nil)\n" );
X
X      if( iset->ic_dfa )
X	 printf( "dfa: %s\n", iset->ic_dfa->dl_meta->CE_NAME );
X      else
X	 printf( "dfa: (nil)\n" );
X
X      printf( "sdr: %04x\n", iset->ic_setdirroot );
X      _dump_dfa_stack(iset->ic_dfastack.df_set, &iset->ic_dfastack);
X
X      printf( "dmax: %d\n", iset->ic_dmax );
X      printf( "name: %s\n", iset->ic_name );
X      printf( "dir:  %s\n", iset->ic_dir?iset->ic_dir:"(nil)" );
X
X      printf( "parent: " );
X      if( iset->ic_parent )
X	if( iset->ic_parent->ic_meta )
X	   printf( "%s --> %s\n",
X	           iset->ic_parent->ic_meta->CE_NAME,
X		   iset->ic_parent->ic_meta->ce_prq ?
X		   iset->ic_parent->ic_meta->ce_prq->cl_prq->CE_NAME :
X		   "(nil)" );
X	else
X	   printf( "(nil)\n" );
X      else
X	 printf( "(nil)\n" );
X   }
X   printf( "==================================\n" );
}
#endif
SHAR_EOF
chmod 0640 dmake/infer.c ||
echo 'restore of dmake/infer.c failed'
Wc_c="`wc -c < 'dmake/infer.c'`"
test 24179 -eq "$Wc_c" ||
	echo 'dmake/infer.c: original size 24179, current size' "$Wc_c"
rm -f _shar_wnt_.tmp
fi
# ============= dmake/itypes.h ==============
if test -f 'dmake/itypes.h' -a X"$1" != X"-c"; then
	echo 'x - skipping dmake/itypes.h (File already exists)'
	rm -f _shar_wnt_.tmp
else
> _shar_wnt_.tmp
sed 's/^X//' << 'SHAR_EOF' > 'dmake/itypes.h' &&
/* RCS      -- $Header: /u2/dvadura/src/generic/dmake/src/RCS/itypes.h,v 1.1 91/05/06 15:23:18 dvadura Exp $
-- SYNOPSIS -- type declarations for common types
-- 
-- DESCRIPTION
-- 	portable type declarations.
--
-- AUTHOR
--      Dennis Vadura, dvadura@watdragon.uwaterloo.ca
--      CS DEPT, University of Waterloo, Waterloo, Ont., Canada
--
-- COPYRIGHT
--      Copyright (c) 1990 by Dennis Vadura.  All rights reserved.
-- 
--      This program is free software; you can redistribute it and/or
--      modify it under the terms of the GNU General Public License
--      (version 1), as published by the Free Software Foundation, and
--      found in the file 'LICENSE' included with this distribution.
-- 
--      This program is distributed in the hope that it will be useful,
--      but WITHOUT ANY WARRANTY; without even the implied warrant of
--      MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
--      GNU General Public License for more details.
-- 
--      You should have received a copy of the GNU General Public License
--      along with this program;  if not, write to the Free Software
--      Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
--
-- LOG
--     $Log:	itypes.h,v $
X * Revision 1.1  91/05/06  15:23:18  dvadura
X * dmake Release Version 3.7
X * 
*/
X
X
#ifndef ITYPES_h
#define	ITYPES_h
X
#if defined(M_I86) || defined(MC68000)
typedef char  int8;               /* typedefs for right size ints */
typedef int   int16;
typedef long  int32;
typedef unsigned char  uint8;
typedef unsigned int   uint16;
typedef unsigned long  uint32;
#else
typedef char  int8;               /* typedefs for right size ints */
typedef short int16;
typedef long  int32;
typedef unsigned char  uint8;
typedef unsigned short uint16;
typedef unsigned long  uint32;
#endif
X
#endif
X
SHAR_EOF
chmod 0640 dmake/itypes.h ||
echo 'restore of dmake/itypes.h failed'
Wc_c="`wc -c < 'dmake/itypes.h'`"
test 1809 -eq "$Wc_c" ||
	echo 'dmake/itypes.h: original size 1809, current size' "$Wc_c"
rm -f _shar_wnt_.tmp
fi
# ============= dmake/macparse.c ==============
if test -f 'dmake/macparse.c' -a X"$1" != X"-c"; then
	echo 'x - skipping dmake/macparse.c (File already exists)'
	rm -f _shar_wnt_.tmp
else
> _shar_wnt_.tmp
sed 's/^X//' << 'SHAR_EOF' > 'dmake/macparse.c' &&
/* RCS      -- $Header: /u2/dvadura/src/generic/dmake/src/RCS/macparse.c,v 1.1 91/05/06 15:23:18 dvadura Exp $
-- SYNOPSIS -- parse a macro definition
-- 
-- DESCRIPTION
--	This file contains the code that parses a macro definition
--	stored in a buffer.  If the string in buffer is not a valid
--	macro definition the routie Parse_macro returns 0, otherwise it
--	returns 1 to indicate success.
-- 
-- AUTHOR
--      Dennis Vadura, dvadura@watdragon.uwaterloo.ca
--      CS DEPT, University of Waterloo, Waterloo, Ont., Canada
--
-- COPYRIGHT
--      Copyright (c) 1990 by Dennis Vadura.  All rights reserved.
-- 
--      This program is free software; you can redistribute it and/or
--      modify it under the terms of the GNU General Public License
--      (version 1), as published by the Free Software Foundation, and
--      found in the file 'LICENSE' included with this distribution.
-- 
--      This program is distributed in the hope that it will be useful,
--      but WITHOUT ANY WARRANTY; without even the implied warrant of
--      MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
--      GNU General Public License for more details.
-- 
--      You should have received a copy of the GNU General Public License
--      along with this program;  if not, write to the Free Software
--      Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
--
-- LOG
--     $Log:	macparse.c,v $
X * Revision 1.1  91/05/06  15:23:18  dvadura
SHAR_EOF
true || echo 'restore of dmake/macparse.c failed'
fi
echo 'End of part 10, continue with part 11'
echo 11 > _shar_seq_.tmp
exit 0

exit 0 # Just in case...
-- 
Kent Landfield                   INTERNET: kent@sparky.IMD.Sterling.COM
Sterling Software, IMD           UUCP:     uunet!sparky!kent
Phone:    (402) 291-8300         FAX:      (402) 291-4362
Please send comp.sources.misc-related mail to kent@uunet.uu.net.