1/* @(#)xgrun.pl	24.1 2/23/88 */
    2
    3/* 
    4	Copyright 1986, Fernando C.N. Pereira and David H.D. Warren,
    5
    6			   All Rights Reserved
    7|	Copyright (C) 1982						  |
    8|									  |
    9|	David Warren,							  |
   10|		SRI International, 333 Ravenswood Ave., Menlo Park,	  |
   11|		California 94025, USA;					  |
   12|									  |
   13|	Fernando Pereira,						  |
   14|		Dept. of Architecture, University of Edinburgh,		  |
   15|		20 Chambers St., Edinburgh EH1 1JZ, Scotland		  |
   16|									  |
   17|	This program may be used, copied, altered or included in other	  |
   18|	programs only for academic purposes and provided that the	  |
   19|	authorship of the initial program is aknowledged.		  |
   20|	Use for commercial purposes without the previous written 	  |
   21|	agreement of the authors is forbidden.				  |
   22|_________________________________________________________________________|
   23
   24*/
   25
   26/*
   27:- op(1001,xfy,...).
   28:- op(1101,xfx,'--->').
   29:- op(500,fx,+).
   30:- op(500,fx,-).
   31*/
   32:- mode((terminal(?,+,?,+,?),
   33        gap(+),
   34        virtual(+,+,?))).   35
   36terminal(T,S,S,x(_,terminal,T,X),X).
   37terminal(T,[T|S],S,X,X) :-
   38   gap(X).
   39
   40gap(x(gap,_,_,_)).
   41gap([]).
   42
   43virtual(NT,x(_,nonterminal,NT,X),X).
   44
   45phraseXG(P,A1,A2,A3,A4):-
   46   safe_univ(P,[F|Args0]),
   47   dtrace,
   48   conc_gx(Args0,[A1,A2,A3,A4],Args),
   49   Q=..[F|Args], 
   50   call(Q)