[unix-pc.sources] gnuplot.shar.04

jdc@naucse.UUCP (John Campbell) (09/04/89)

#! /bin/sh
# This is a shell archive.  Remove anything before this line, then unpack
# it by saving it into a file and typing "sh file".  To overwrite existing
# files, type "sh file -c".  You can also feed this as standard input via
# unshar, or by typing "sh <file", e.g..  If this archive is complete, you
# will see the following message at the end:
#		"End of archive 4 (of 7)."
# Contents:  ./graphics.c ./hrcgraph.asm ./parse.c ./unixpc.trm
#   ./util.c
# Wrapped by jdc@naucse on Mon Sep  4 09:22:34 1989
PATH=/bin:/usr/bin:/usr/ucb ; export PATH
if test -f './graphics.c' -a "${1}" != "-c" ; then 
  echo shar: Will not clobber existing file \"'./graphics.c'\"
else
echo shar: Extracting \"'./graphics.c'\" \(9002 characters\)
sed "s/^X//" >'./graphics.c' <<'END_OF_FILE'
X/*
X *
X *    G N U P L O T  --  graphics.c
X *
X *  Copyright (C) 1986, 1987  Thomas Williams, Colin Kelley
X *
X *  You may use this code as you wish if credit is given and this message
X *  is retained.
X *
X *  Please e-mail any useful additions to vu-vlsi!plot so they may be
X *  included in later releases.
X *
X *  This file should be edited with 4-column tabs!  (:set ts=4 sw=4 in vi)
X */
X
X#include <stdio.h>
X#include <math.h>
X#include "plot.h"
X
Xchar *strcpy(),*strncpy(),*strcat();
X
Xextern BOOLEAN polar;
Xextern BOOLEAN autoscale;
Xextern FILE *outfile;
Xextern BOOLEAN log_x, log_y;
Xextern int term;
X
Xextern BOOLEAN screen_ok;
Xextern BOOLEAN term_init;
X
Xextern double loff,roff,toff,boff;
Xextern double zero;
X
Xextern struct termentry term_tbl[];
X
X
X#ifndef max		/* Lattice C has max() in math.h, but shouldn't! */
X#define max(a,b) ((a > b) ? a : b)
X#endif
X
X/* maps floating point x (and y) to screen */ 
X#define map_x(x) (int)((x-xmin)*xscale) 
X#define map_y(y) (int)((y-ymin)*yscale)
X
X
Xdouble raise(x,y)
Xdouble x;
Xint y;
X{
Xregister int i;
Xdouble val;
X
X	val = 1.0;
X	for (i=0; i < abs(y); i++)
X		val *= x;
X	if (y < 0 ) return (1.0/val);
X	return(val);
X}
X
X
Xdouble make_tics(tmin,tmax,logscale)
Xdouble tmin,tmax;
XBOOLEAN logscale;
X{
Xregister double xr,xnorm,tics,tic,l10;
X
X	xr = fabs(tmin-tmax);
X	
X	l10 = log10(xr);
X	if (logscale) {
X		tic = raise(10.0,(l10 >= 0.0 ) ? (int)l10 : ((int)l10-1));
X		if (tic < 1.0)
X			tic = 1.0;
X	} else {
X		xnorm = pow(10.0,l10-(double)((l10 >= 0.0 ) ? (int)l10 : ((int)l10-1)));
X		if (xnorm <= 2)
X			tics = 0.2;
X		else if (xnorm <= 5)
X			tics = 0.5;
X		else tics = 1.0;	
X		tic = tics * raise(10.0,(l10 >= 0.0 ) ? (int)l10 : ((int)l10-1));
X	}
X	return(tic);
X}
X
Xchar *idx(a,b)
Xchar *a,b;
X{
X	do {
X		if (*a == b)
X			return(a);
X	} while (*a++);
X	return(0);
X}
X
X 
Xnum2str(num,str)
Xdouble num;
Xchar str[];
X{
Xstatic char temp[80];
Xregister double d;
Xregister char *a,*b;
X
X 	if ((d = fabs(num)) > 9999.0 || d < 0.001 && d != 0.0) 
X		(void) sprintf(temp,"%-.3e",num);	
X	else
X		(void) sprintf(temp,"%-.3g",num);
X	if (b = idx(temp,'e')) {
X		a = b;
X		while ( *(--a) == '0') /* trailing zeros */
X			;	
X		if ( *a == '.') 
X			a--;
X		(void) strncpy(str,temp,(int)(a-temp)+1);
X		str[(int)(a-temp)+1] = '\0';
X		a = b+1;	/* point to 1 after 'e' */
X		(void) strcat(str,"e");
X		if ( *a == '-') 
X			(void) strcat(str,"-");
X		a++;						 /* advance a past '+' or '-' */
X		while ( *a == '0' && *(a+1) != '\0') /* leading zeroes */
X			a++;
X		(void) strcat(str,a); /* copy rest of string */
X	}
X	else
X		(void) strcpy(str,temp);	
X}
X
X
Xdo_plot(plots, pcount, xmin, xmax, ymin, ymax)
Xstruct curve_points *plots;
Xint pcount;			/* count of plots in linked list */
Xdouble xmin, xmax;
Xdouble ymin, ymax;
X{
Xregister int i, x;
Xregister struct termentry *t = &term_tbl[term];
Xregister BOOLEAN prev_undef;
Xregister int curve, xaxis_y, yaxis_x, dpcount;
Xregister struct curve_points *this_plot;
Xregister enum PLOT_TYPE p_type;
Xregister double xscale, yscale;
Xregister double ytic, xtic, least, most, ticplace;
Xregister int mms,mts;
X			/* only a Pyramid would have this many registers! */
Xstatic char xns[20],xms[20],yns[20],yms[20],xts[20],yts[20];
Xstatic char label[80];
X
X	if (polar)
X		polar_xform (plots, pcount, &xmin, &xmax, &ymin, &ymax);
X
X	if (ymin == HUGE || ymax == -HUGE)
X		int_error("all points undefined!", NO_CARET);
X
X/*	This used be xmax == xmin, but that caused an infinite loop once. */
X	if (fabs(xmax - xmin) < zero)
X		int_error("xmin should not equal xmax!",NO_CARET);
X	if (fabs(ymax - ymin) < zero)
X		int_error("ymin should not equal ymax!",NO_CARET);
X
X/*	Apply the desired viewport offsets. */
X	xmin -= loff;
X	xmax += roff;
X	ymin -= boff;
X	ymax += toff;
X	
X	ytic = make_tics(ymin,ymax,log_y);
X	xtic = make_tics(xmin,xmax,log_x);
X	dpcount = 0;
X	
X	if (ymin < ymax ) {
X		ymin = ytic * floor(ymin/ytic);	
X		ymax = ytic * ceil(ymax/ytic);
X	}
X	else {
X		ymin = ytic * ceil(ymin/ytic);
X		ymax = ytic * floor(ymax/ytic);
X	}
X
X	yscale = (t->ymax - 2)/(ymax - ymin);
X	xscale = (t->xmax - 2)/(xmax - xmin);
X	
X	if (!term_init) {
X		(*t->init)();
X		term_init = TRUE;
X	}
X	screen_ok = FALSE;
X	(*t->graphics)();
X	(*t->linetype)(-2); /* border linetype */
X
X	/* draw plot border */
X	(*t->move)(0,0);	
X	(*t->vector)(t->xmax-1,0);	
X	(*t->vector)(t->xmax-1,t->ymax-1);	
X	(*t->vector)(0,t->ymax-1);	
X	(*t->vector)(0,0);
X
X	least = (ymin < ymax) ? ymin : ymax;
X	most = (ymin < ymax) ? ymax : ymin;
X
X	for (ticplace = ytic + least; ticplace < most ; ticplace += ytic) { 
X		(*t->move)(0,map_y(ticplace));
X		(*t->vector)(t->h_tic,map_y(ticplace));
X		(*t->move)(t->xmax-1,map_y(ticplace));
X       	        (*t->vector)(t->xmax-1-t->h_tic,map_y(ticplace));
X	}
X
X	if (xmin < xmax ) {
X		least = xtic * floor(xmin/xtic);	
X		most = xtic * ceil(xmax/xtic);
X	}
X	else {
X		least = xtic * ceil(xmin/xtic);
X		most = xtic * floor(xmax/xtic);
X	}
X
X	for (ticplace = xtic + least; ticplace < most ; ticplace += xtic) { 
X		(*t->move)(map_x(ticplace),0);
X		(*t->vector)(map_x(ticplace),t->v_tic);
X		(*t->move)(map_x(ticplace),t->ymax-1);
X       	        (*t->vector)(map_x(ticplace),t->ymax-1-t->v_tic);
X	}
X
X	if (log_x) {
X		num2str(pow(10.0,xmin),xns);
X		num2str(pow(10.0,xmax),xms);
X		num2str(pow(10.0,xtic),xts);
X	}
X	else {
X		num2str(xmin,xns);
X		num2str(xmax,xms);
X		num2str(xtic,xts);
X	}
X	if (log_y) {
X		num2str(pow(10.0,ymin),yns);
X		num2str(pow(10.0,ymax),yms);
X		num2str(pow(10.0,ytic),yts);
X	} else {
X		num2str(ymin,yns);
X		num2str(ymax,yms);
X		num2str(ytic,yts);
X	}
X	mms = max(strlen(xms),strlen(yms));
X	mts = max(strlen(xts),strlen(yts));
X
X	(void) sprintf(label,"%s < y < %-*s  inc = %-*s",yns,mms,yms,mts,yts);
X	(*t->lrput_text)(0, label);
X	(void) sprintf(label,"%s < x < %-*s  inc = %-*s",xns,mms,xms,mts,xts);
X	(*t->lrput_text)(1, label);
X
X
X/* DRAW AXES */
X	(*t->linetype)(-1);	/* axis line type */
X	xaxis_y = map_y(0.0);
X	yaxis_x = map_x(0.0); 
X
X	if (xaxis_y < 0)
X		xaxis_y = 0;				/* save for impulse plotting */
X	else if (xaxis_y >= t->ymax)
X		xaxis_y = t->ymax - 1;
X	else if (!log_y) {
X		(*t->move)(0,xaxis_y);
X		(*t->vector)((t->xmax-1),xaxis_y);
X	}
X
X	if (!log_x && yaxis_x >= 0 && yaxis_x < t->xmax) {
X		(*t->move)(yaxis_x,0);
X		(*t->vector)(yaxis_x,(t->ymax-1));
X	}
X
X/* DRAW CURVES */
X	this_plot = plots;
X	for (curve = 0; curve < pcount; this_plot = this_plot->next_cp, curve++) {
X		(*t->linetype)(curve);
X		(*t->ulput_text)(curve, this_plot->title);
X		(*t->linetype)(curve);
X
X		p_type = this_plot->plot_type;
X		switch(this_plot->plot_style) {
X			case IMPULSES:
X				for (i = 0; i < this_plot->p_count; i++) {
X					if (!this_plot->points[i].undefined) {
X						x = map_x(this_plot->points[i].x);
X						(*t->move)(x,xaxis_y);
X						(*t->vector)(x,map_y(this_plot->points[i].y));
X					}
X				}
X				break;
X			case LINES:
X				prev_undef = TRUE;
X				for (i = 0; i < this_plot->p_count; i++) {
X					if (!this_plot->points[i].undefined) {
X						x = map_x(this_plot->points[i].x);
X						if (prev_undef)
X							(*t->move)(x,
X							map_y(this_plot->points[i].y));
X						(*t->vector)(x,
X							map_y(this_plot->points[i].y));
X					}
X					prev_undef = this_plot->points[i].undefined;
X				}
X				break;
X			case POINTS:
X				for (i = 0; i < this_plot->p_count; i++) {
X					if (!this_plot->points[i].undefined) {
X						x = map_x(this_plot->points[i].x);
X						(*t->point)(x,map_y(this_plot->points[i].y),dpcount);
X					}
X				}
X				dpcount++;
X				break;
X		}
X	}
X	(*t->text)();
X	(void) fflush(outfile);
X}
X
X
Xpolar_xform (plots, pcount, xminp, xmaxp, yminp, ymaxp)
Xstruct curve_points *plots;
Xint pcount;			/* count of plots in linked list */
Xdouble *xminp, *xmaxp;
Xdouble *yminp, *ymaxp;
X{
Xregister int i, p_cnt;
Xregister struct termentry *t = &term_tbl[term];
Xregister struct curve_points *this_plot;
Xenum PLOT_TYPE p_type;
Xstruct coordinate *pnts;
Xint curve, xaxis_y, yaxis_x, dpcount;
Xdouble xmin, xmax, ymin, ymax, x, y;
X
X/*
X	Cycle through all the plots converting polar to rectangular and adjust
X	max and mins.
X*/
X	xmin = HUGE;
X	ymin = HUGE;
X	xmax = -HUGE;
X	ymax = -HUGE;
X    
X	this_plot = plots;
X	for (curve = 0; curve < pcount; this_plot = this_plot->next_cp, curve++) {
X		p_cnt = this_plot->p_count;
X        pnts = this_plot->points;
X
X	/*	Convert to cartesian all points in this curve. */
X		for (i = 0; i < p_cnt; i++) {
X			if (!pnts[i].undefined) {
X				x = pnts[i].y*cos(pnts[i].x);
X				y = pnts[i].y*sin(pnts[i].x);
X				pnts[i].x = x;
X				pnts[i].y = y;
X				if (xmin > x) xmin = x;
X				if (xmax < x) xmax = x;
X			/*  Can't worry about autoscale (assume true). */
X				if (ymin > y) ymin = y;
X				if (ymax < y) ymax = y;
X			}
X		}	
X	}
X	if (xmin < xmax) {  /* All points might be undefined... */
X		if (xmax - xmin < zero) {
X		/* This happens at least for the plot of 1/cos(x) (verticle line). */
X			xmin -= 3.14159;
X			xmax += 3.14159;
X		}
X	}
X	if (ymin < ymax) {  /* Only if there were defined points... */
X		if (ymax - ymin < zero) {
X		/* This happens at least for the plot of 1/sin(x) (horizontal line). */
X			ymin -= 1;
X			ymax += 1;
X		}
X	}
X
X/* Return the new maximums and minimums */
X	*xminp = xmin;
X	*xmaxp = xmax;
X	*yminp = ymin;
X	*ymaxp = ymax;
X}
END_OF_FILE
if test 9002 -ne `wc -c <'./graphics.c'`; then
    echo shar: \"'./graphics.c'\" unpacked with wrong size!
fi
# end of './graphics.c'
fi
if test -f './hrcgraph.asm' -a "${1}" != "-c" ; then 
  echo shar: Will not clobber existing file \"'./hrcgraph.asm'\"
else
echo shar: Extracting \"'./hrcgraph.asm'\" \(7978 characters\)
sed "s/^X//" >'./hrcgraph.asm' <<'END_OF_FILE'
XTITLE	Hercules graphics module
X
X;	Michael Gordon - 8-Dec-86
X;
X; Certain routines were taken from the Hercules BIOS of	Dave Tutelman - 8/86
X; Others came from pcgraph.asm included in GNUPLOT by Colin Kelley
X;
X; modified slightly by Colin Kelley - 22-Dec-86
X;	added header.mac, parameterized declarations
X; added dgroup: in HVmodem to reach HCh_Parms and HGr_Parms - 30-Jan-87
X
Xinclude header.mac
X
Xif1
Xinclude lineproc.mac
Xendif
X
X
XGPg1_Base equ 0B800h	; Graphics page 1 base address
X
X_text	segment
X
X	public _H_line, _H_color, _H_mask, _HVmode, _H_puts
X
Xhpixel	proc near
X	ror word ptr bmask,1
X	jc cont
X	ret
Xcont:
X	push ax
X	push bx
X	push cx
X	push dx
X	push si
X	mov cx,ax		; x
X	mov dx,bx		; y
X;
X; [couldn't this be done faster with a lookup table? -cdk]
X;
X	; first compute the address of byte to be modified
X	; = 90*[row/4] + [col/8] + 2^D*[row/4] + 2^F*page
X	mov	bh,cl		; col (low order) in BH
X	mov	bl,dl		; row (low order) in BL
X	and	bx,0703H	; mask the col & row remainders
XIFDEF iAPX286
X	shr	cx,3		; col / 8
X	shr	dx,2		; row / 4
X	mov	al,90
X	mul	dx		; AX = 90*[ row/4 ]
X	add	ax,cx		;  ... + col/8
X	shl	bl,5		; align row remainder
XELSE			; same as above, obscure but fast for 8086
X	shr	cx,1		; divide col by 8
X	shr	cx,1
X	shr	cx,1
X	shr	dx,1		; divide row by 4
X	shr	dx,1
X	shl	dx,1		; begin fast multiply by 90 (1011010 B)
X	mov	ax,dx
X	shl	dx,1
X	shl	dx,1
X	add	ax,dx
X	shl	dx,1
X	add	ax,dx
X	shl	dx,1
X	shl	dx,1
X	add	ax,dx		; end fast multiply by 90
X	add	ax,cx		; add on the col/8
X	shl	bl,1		; align row remainder
X	shl	bl,1
X	shl	bl,1
X	shl	bl,1
X	shl	bl,1
XENDIF
X	add	ah,bl		; use aligned row remainder
Xend_adr_calc:			; address of byte is now in AX
X	mov	dx,GPg1_Base	; base of pixel display to DX
X	mov	es,dx		; ...and thence to segment reg
X	mov	si,ax		; address of byte w/ pixel to index reg
X	mov	cl,bh		; bit addr in byte
X	mov	al,80H		; '1000 0000' in AL 
X	shr	al,cl		; shift mask to line up with bit to read/write
Xset_pix:			; set the pixel
X	or	es:[si],al	; or the mask with the right byte
X	pop si
X	pop dx
X	pop cx
X	pop bx
X	pop ax
X	ret
Xhpixel endp
X
Xlineproc _H_line, hpixel
X
X;
X; clear - clear page 1 of the screen buffer to zero (effectively, blank
X;	the screen)
X;
Xclear   proc near
X	push es
X	push ax
X	push cx
X	push di
X	mov ax, GPg1_Base
X	mov es, ax
X	xor di, di
X	mov cx, 4000h
X	xor ax, ax
X	cld
X	rep stosw			; zero out screen page
X	pop di
X	pop cx
X	pop ax
X	pop es
X	ret
Xclear	endp
X
Xbeginproc _H_color
X	push bp
X	mov bp,sp
X	mov al,[bp+X]			; color
X	mov byte ptr color,al
X	pop bp
X	ret
X_H_color endp
X
Xbeginproc _H_mask
X	push bp
X	mov bp,sp
X	mov ax,[bp+X]			; mask
X	mov word ptr bmask,ax
X	pop bp
X	ret
X_H_mask endp
X
XHCtrl_Port	equ	03B8H	; Hercules 6845 control port IO addr
XHIndx_Port	equ	03B4H	; Hercules 6845 index port IO addr
XHScrn_Enable	equ	008h	; Control port bit to enable video
XHCh_Mode	equ	020h	; Character output mode
XHGr_Mode	equ	082h	; Graphics output mode page 1
X
Xparm_count equ 12
X
Xbeginproc _HVmode
X	push bp
X	mov bp, sp
X	push si
X	mov ax, [bp+X]
X	or ah, al
X	mov al, HCh_Mode		; Assume character mode is wanted
X	mov si, offset dgroup:HCh_Parms
X	cmp ah, 0			; nonzero means switch to graphics
X	jz vmode_ok
X	call near ptr clear		; clear the graphics page
X	mov al, HGr_Mode
X	mov si, offset dgroup:HGr_Parms
Xvmode_ok:
X	mov dx, HCtrl_Port
X	out dx, al			; Set Hercules board to proper mode
X	call near ptr setParms		; Set the 6845 parameters
X	or al, HScrn_Enable		; Enable the video output
X	out dx, al
X	pop si
X	pop bp
X	ret
X_HVmode	endp
X
XsetParms proc near		; Send 6845 parms to Hercules board
X	push ax
X	push dx
X	push si			
X	mov dx, HIndx_Port	; Index port addr -> DX
X	mov ah, 0		; 0 -> parameter counter
Xsp_loop:
X	mov al, ah
X	out dx, al		; output to 6845 addr register
X	inc dx			; next output to data register
X	mov al, [si]		; next control byte -> al
X	inc si
X	out dx, al		; output control byte
X	dec dx			; 6845 index addr -> dx
X	inc ah			; bump addr
X	cmp ah, parm_count
X	jnz sp_loop
X	pop si
X	pop dx
X	pop ax
X	ret
XsetParms endp
X
X; H_puts - print text in graphics mode
X;
X;	cx = row
X;	bx = column
X;	si = address of string (null terminated) to print
X
Xbeginproc _H_puts
X	push bp
X	mov bp, sp
X	push si
X	push ds
X	mov si, [bp+X]			; string offset
X
Xifdef LARGE_DATA
X	mov ds, [bp+X+2]		; string segment
X	mov cx, [bp+X+4]		; row
X	mov bx, [bp+X+6]		; col
Xelse
X	mov cx, [bp+X+2]		; row
X	mov bx, [bp+X+4]		; col
Xendif
X
Xploop:	lodsb				; get next char
X	or	al, al			; end of display?
X	je	pdone
X	call near ptr display
X	inc	bx			; bump to next column
X	jmp	ploop
Xpdone:	pop ds
X	pop si
X	pop bp
X	ret
X_H_puts	endp
X
X;
X; display - output an 8x8 character from the IBM ROM to the Herc board
X;
X; AX = char, BX = column (0-89), CX = row(0-42)  ** all preserved **
X;
XCON8	db	8
XCON180	db	180
XIBMROM	equ	0F000h
XCHARTAB	equ	0FA6Eh
X
Xdisplay	proc near
X	push	ds			; save the lot
X	push	es
X	push	ax
X	push	bx
X	push	cx
X	push	dx
X	push	si
X	push	di
X
X; setup ds -> IBM ROM, and si -> index into IBM ROM character table located
X;	at 0fa6eh in the ROM
X
X	and	ax, 07fh
X	mul	cs:CON8			; mult by 8 bytes of table per char
X	mov	si, ax
X	mov	ax, IBMROM
X	mov	ds, ax
X	assume	ds:nothing
X	add	si, CHARTAB		; add offset of character table
X
X; compute index into Hercules screen memory for scan line 0.  The remaining
X;	seven scan lines are all at fixed offsets from the first.
X;
X;	Since graphics mode treats the screen as sets of 16x4 "characters",
X;	we need to map an 8x8 real character onto the front or back of
X;	a pair of graphics "characters".  The first four scan lines of our
X;	8x8 character will map to the top graphics "character", and the second
X;	four scan lines map to the graphics character on the "line" (4 scan
X;	lines high) below it.
X;
X;	For some exotic hardware reason (probably speed), all scan line 0
X;	bits (i.e. every fourth scan line) are stored in memory locations
X;	0-2000h in the screen buffer.  All scan line 1 bits are stored
X;	2000h-4000h.  Within these banks, they are stored by rows.  The first
X;	scan line on the screen (scan line 0 of graphics character row 0)
X;	is the first 45 words of memory in the screen buffer.  The next 45
X;	words are the first scan line graphics row 1, and since graphics
X;	"characters" are 4 bits high, this second scan line is physically
X;	the fifth scan line displayed on the screen.
X;
X;	SO, to display an 8x8 character, the 1st and 5th rows of dots are
X;	both scan line 0 of the graphics "character", the 2nd and 6th are
X;	scan line 1, and so on.
X;
X;	The column (0-89) tells which byte in a scan line we need to load.
X;	Since it takes two rows of graphics characters to hold one row of
X;	our characters, column+90 is a index to scan line 4 rows of pixels
X;	higher (n+4).  Thus 180 bytes of screen memory in any bank (0h, 2000h,
X;	4000h, 6000h) represent a row of 8x8 characters.
X;	
X;	The starting location in screen memory for the first scan line of
X;	a character to be displayed will be:  	(row*180)+column
X;	The 5th scan line will be at:		(row*180)+column+90
X;
X;	The second and 6th scan lines will be at the above offsets plus
X;	the bank offset of 2000h.  The third and 7th, add 4000h and finally
X;	the 4th and 8th, add 6000h.
X;
X	mov	ax, GPg1_Base
X	mov	es, ax			; es = hercules page 0
X	mov	ax, cx			; get row
X	mul	cs:CON180		; mult by 180(10)
X	mov	di, ax			; di = index reg
X	cld				; insure right direction
X
X;output 8 segments of character to video ram
X
X	lodsb				; line 0
X	mov	es:[di+bx], al
X	lodsb
X	mov	es:[di+bx+2000h], al	; line 1
X	lodsb
X	mov	es:[di+bx+4000h], al	; line 2
X	lodsb
X	mov	es:[di+bx+6000h], al	; line 3
X	lodsb
X	mov	es:[di+bx+90], al	; line 4
X	lodsb
X	mov	es:[di+bx+2000h+90], al	; line 5
X	lodsb
X	mov	es:[di+bx+4000h+90], al	; line 6
X	lodsb
X	mov	es:[di+bx+6000h+90], al	; line 7
X
X	pop	di
X	pop	si
X	pop	dx
X	pop	cx
X	pop	bx
X	pop	ax
X	pop	es
X	pop	ds
X	ret
Xdisplay	endp
X
X_text	ends
X
X_data	segment
Xbmask	dw -1
Xcolor	db 1
X_data	ends
X
Xconst	segment
XHCh_Parms db 	61H, 50H, 52H, 0FH, 19H, 06H, 19H, 19H, 02H, 0DH, 0BH, 0CH
XHGr_Parms db	35H, 2DH, 2EH, 07H, 5BH, 02H, 57H, 57H, 02H, 03H, 00H, 00H
Xconst	ends
X
X	end
X---------------------------end HRCGRAPH.ASM-------------------------------
X
X
END_OF_FILE
if test 7978 -ne `wc -c <'./hrcgraph.asm'`; then
    echo shar: \"'./hrcgraph.asm'\" unpacked with wrong size!
fi
# end of './hrcgraph.asm'
fi
if test -f './parse.c' -a "${1}" != "-c" ; then 
  echo shar: Will not clobber existing file \"'./parse.c'\"
else
echo shar: Extracting \"'./parse.c'\" \(7828 characters\)
sed "s/^X//" >'./parse.c' <<'END_OF_FILE'
X/*
X *
X *    G N U P L O T  --  parse.c
X *
X *  Copyright (C) 1986, 1987  Colin Kelley, Thomas Williams
X *
X *  You may use this code as you wish if credit is given and this message
X *  is retained.
X *
X *  Please e-mail any useful additions to vu-vlsi!plot so they may be
X *  included in later releases.
X *
X *  This file should be edited with 4-column tabs!  (:set ts=4 sw=4 in vi)
X */
X
X#include <stdio.h>
X#include <setjmp.h>
X#include <signal.h>
X#include <errno.h>
X#include "plot.h"
X
Xextern BOOLEAN undefined;
X
X#ifndef vms
Xextern int errno;
X#endif
X
Xextern int num_tokens,c_token;
Xextern struct lexical_unit token[];
Xextern char c_dummy_var[];			/* name of current dummy variable */
Xextern struct udft_entry *dummy_func;	/* pointer to dummy variable's func */
X
Xchar *malloc();
X
Xstruct value *pop(),*integer(),*complex();
Xstruct at_type *temp_at(), *perm_at();
Xstruct udft_entry *add_udf();
Xstruct udvt_entry *add_udv();
Xunion argument *add_action();
X
Xstruct at_type at;
Xstatic jmp_buf fpe_env;
X
X#define dummy (struct value *) 0
X#ifdef __TURBOC__
Xvoid fpe(int xXx)
X#else
Xfpe()
X#endif
X{
X#ifdef PC	/* thanks to lotto@wjh12.UUCP for telling us about this  */
X	_fpreset();
X#endif
X	(void) signal(SIGFPE, fpe);
X	undefined = TRUE;
X	longjmp(fpe_env, TRUE);
X}
X
X
Xevaluate_at(at_ptr,val_ptr)
Xstruct at_type *at_ptr;
Xstruct value *val_ptr;
X{
X	undefined = FALSE;
X	errno = 0;
X	reset_stack();
X	if (setjmp(fpe_env))
X		return;				/* just bail out */
X	(void) signal(SIGFPE, fpe);	/* catch core dumps on FPEs */
X
X	execute_at(at_ptr);
X
X	(void) signal(SIGFPE, SIG_DFL);
X
X	if (errno == EDOM || errno == ERANGE) {
X		undefined = TRUE;
X	} else {
X		(void) pop(val_ptr);
X		check_stack();
X	}
X}
X
X
Xstruct value *
Xconst_express(valptr)
Xstruct value *valptr;
X{
Xregister int tkn = c_token;
X	if (END_OF_COMMAND)
X		int_error("constant expression required",c_token);
X	evaluate_at(temp_at(),valptr);	/* run it and send answer back */
X	if (undefined) {
X		int_error("undefined value",tkn);
X	}
X	return(valptr);
X}
X
X
Xstruct at_type *
Xtemp_at()	/* build a static action table and return its pointer */
X{
X	at.a_count = 0;		/* reset action table !!! */
X	express();
X	return(&at);
X}
X
X
X/* build an action table, put it in dynamic memory, and return its pointer */
X
Xstruct at_type *
Xperm_at()
X{
Xregister struct at_type *at_ptr;
Xregister unsigned int len;
X
X	(void) temp_at();
X	len = sizeof(struct at_type) -
X		(MAX_AT_LEN - at.a_count)*sizeof(struct at_entry);
X	if (at_ptr = (struct at_type *) malloc(len))
X		(void) memcpy(at_ptr,&at,len);
X	return(at_ptr);
X}
X
X
X#ifdef NOCOPY
X/*
X * cheap and slow version of memcpy() in case you don't have one
X */
Xmemcpy(dest,src,len)
Xchar *dest,*src;
Xunsigned int len;
X{
X	while (len--)
X		*dest++ = *src++;
X}
X#endif /* NOCOPY */
X
X
Xexpress()  /* full expressions */
X{
X	xterm();
X	xterms();
X}
X
Xxterm()  /* ? : expressions */
X{
X	aterm();
X	aterms();
X}
X
X
Xaterm()
X{
X	bterm();
X	bterms();
X}
X
X
Xbterm()
X{
X	cterm();
X	cterms();
X}
X
X
Xcterm()
X{
X	dterm();
X	dterms();
X}
X
X
Xdterm()
X{	
X	eterm();
X	eterms();
X}
X
X
Xeterm()
X{
X	fterm();
X	fterms();
X}
X
X
Xfterm()
X{
X	gterm();
X	gterms();
X}
X
X
Xgterm()
X{
X	hterm();
X	hterms();
X}
X
X
Xhterm()
X{
X	unary(); /* - things */
X	iterms(); /* * / % */
X}
X
X
Xfactor()
X{
Xregister int value;
X
X	if (equals(c_token,"(")) {
X		c_token++;
X		express();
X		if (!equals(c_token,")"))
X			int_error("')' expected",c_token);
X		c_token++;
X	}
X	else if (isnumber(c_token)) {
X		convert(&(add_action(PUSHC)->v_arg),c_token);
X		c_token++;
X	}
X	else if (isletter(c_token)) {
X		if ((c_token+1 < num_tokens)  && equals(c_token+1,"(")) {
X			value = standard(c_token);
X			if (value) {	/* it's a standard function */
X				c_token += 2;
X				express();
X				if (!equals(c_token,")"))
X					int_error("')' expected",c_token);
X				c_token++;
X				(void) add_action(value);
X			}
X			else {
X				value = c_token;
X				c_token += 2;
X				express();
X				if (!equals(c_token,")"))
X					int_error("')' expected",c_token);
X				c_token++;
X				add_action(CALL)->udf_arg = add_udf(value);
X			}
X		}
X		else {
X			if (equals(c_token,c_dummy_var)) {
X				c_token++;
X				add_action(PUSHD)->udf_arg = dummy_func;
X			}
X			else {
X				add_action(PUSH)->udv_arg = add_udv(c_token);
X				c_token++;
X			}
X		}
X	} /* end if letter */
X	else
X		int_error("invalid expression ",c_token);
X
X	/* add action code for ! (factorial) operator */
X	while (equals(c_token,"!")) {
X		c_token++;
X		(void) add_action(FACTORIAL);
X	}
X	/* add action code for ** operator */
X	if (equals(c_token,"**")) {
X			c_token++;
X			unary();
X			(void) add_action(POWER);
X	}
X
X}
X
X
X
Xxterms()
X{  /* create action code for ? : expressions */
X
X	if (equals(c_token,"?")) {
X		register int savepc1, savepc2;
X		register union argument *argptr1,*argptr2;
X		c_token++;
X		savepc1 = at.a_count;
X		argptr1 = add_action(JTERN);
X		express();
X		if (!equals(c_token,":"))
X			int_error("expecting ':'",c_token);
X		c_token++;
X		savepc2 = at.a_count;
X		argptr2 = add_action(JUMP);
X		argptr1->j_arg = at.a_count - savepc1;
X		express();
X		argptr2->j_arg = at.a_count - savepc2;
X	}
X}
X
X
Xaterms()
X{  /* create action codes for || operator */
X
X	while (equals(c_token,"||")) {
X		register int savepc;
X		register union argument *argptr;
X		c_token++;
X		savepc = at.a_count;
X		argptr = add_action(JUMPNZ);	/* short-circuit if already TRUE */
X		aterm();
X		argptr->j_arg = at.a_count - savepc;/* offset for jump */
X		(void) add_action(BOOL);
X	}
X}
X
X
Xbterms()
X{ /* create action code for && operator */
X
X	while (equals(c_token,"&&")) {
X		register int savepc;
X		register union argument *argptr;
X		c_token++;
X		savepc = at.a_count;
X		argptr = add_action(JUMPZ);	/* short-circuit if already FALSE */
X		bterm();
X		argptr->j_arg = at.a_count - savepc;/* offset for jump */
X		(void) add_action(BOOL);
X	}
X}
X
X
Xcterms()
X{ /* create action code for | operator */
X
X	while (equals(c_token,"|")) {
X		c_token++;
X		cterm();
X		(void) add_action(BOR);
X	}
X}
X
X
Xdterms()
X{ /* create action code for ^ operator */
X
X	while (equals(c_token,"^")) {
X		c_token++;
X		dterm();
X		(void) add_action(XOR);
X	}
X}
X
X
Xeterms()
X{ /* create action code for & operator */
X
X	while (equals(c_token,"&")) {
X		c_token++;
X		eterm();
X		(void) add_action(BAND);
X	}
X}
X
X
Xfterms()
X{ /* create action codes for == and != operators */
X
X	while (TRUE) {
X		if (equals(c_token,"==")) {
X			c_token++;
X			fterm();
X			(void) add_action(EQ);
X		}
X		else if (equals(c_token,"!=")) {
X			c_token++;
X			fterm();
X			(void) add_action(NE);
X		}
X		else break;
X	}
X}
X
X
Xgterms()
X{ /* create action code for < > >= or <= operators */
X	
X	while (TRUE) {
X		/* I hate "else if" statements */
X		if (equals(c_token,">")) {
X			c_token++;
X			gterm();
X			(void) add_action(GT);
X		}
X		else if (equals(c_token,"<")) {
X			c_token++;
X			gterm();
X			(void) add_action(LT);
X		}		
X		else if (equals(c_token,">=")) {
X			c_token++;
X			gterm();
X			(void) add_action(GE);
X		}
X		else if (equals(c_token,"<=")) {
X			c_token++;
X			gterm();
X			(void) add_action(LE);
X		}
X		else break;
X	}
X
X}
X
X
X
Xhterms()
X{ /* create action codes for + and - operators */
X
X	while (TRUE) {
X			if (equals(c_token,"+")) {
X				c_token++;
X				hterm();
X				(void) add_action(PLUS);
X			}
X			else if (equals(c_token,"-")) {
X				c_token++;
X				hterm();
X				(void) add_action(MINUS);
X			}
X			else break;
X	}
X}
X
X
Xiterms()
X{ /* add action code for * / and % operators */
X
X	while (TRUE) {
X			if (equals(c_token,"*")) {
X				c_token++;
X				unary();
X				(void) add_action(MULT);
X			}
X			else if (equals(c_token,"/")) {
X				c_token++;
X				unary();
X				(void) add_action(DIV);
X			}
X			else if (equals(c_token,"%")) {
X				c_token++;
X				unary();
X				(void) add_action(MOD);
X			}
X			else break;
X	}
X}
X
X
Xunary()
X{ /* add code for unary operators */
X	if (equals(c_token,"!")) {
X		c_token++;
X		unary();
X		(void) add_action(LNOT);
X	}
X	else if (equals(c_token,"~")) {
X		c_token++;
X		unary();
X		(void) add_action(BNOT);
X	}
X	else if (equals(c_token,"-")) {
X		c_token++;
X		unary();
X		(void) add_action(UMINUS);
X	}
X	else
X		factor();
X}
END_OF_FILE
if test 7828 -ne `wc -c <'./parse.c'`; then
    echo shar: \"'./parse.c'\" unpacked with wrong size!
fi
# end of './parse.c'
fi
if test -f './unixpc.trm' -a "${1}" != "-c" ; then 
  echo shar: Will not clobber existing file \"'./unixpc.trm'\"
else
echo shar: Extracting \"'./unixpc.trm'\" \(12181 characters\)
sed "s/^X//" >'./unixpc.trm' <<'END_OF_FILE'
X/*
XFrom: John Campbell (...!arizona!naucse!jdc)
X
XI ported gnuplot to the ATT 3b1 (ATT7300) on 12/4/88.  The 3b1, as I view
Xit, is a 720x300 bitmapped, monochrome display (often people don't use
Xthe top 12 scan lines and thus the effective size is 720x288).  I tried to
Xmaximize the size of the graph area, by using these top 12 lines (normally
Xreserved) and set up a signal handler to restore them upon exit, abort, etc.
X
XLine styles were "fudged" (they do not know the aspect ratio).  The same
Xline style may look different depending upon the slope of the curve.  Due to
Xthis only 4 line styles were implemented.  While more line types are possible,
Xthe current styles were chosen as distinguishable.
X
XThe 3b1 has 4 "special" rows at the bottom that I could not use in graphics
Xmode.  I chose to use these lines for the plot scale--normally found at the
Xbottom right corner of the plot.  I wanted to use the four bottom lines as
Xprompt/command lines, but did not find a way to do this.  If someone ever
Xwrites a device driver to "open" these rows as a small separate window, I
Xcould implement my original idea.
X*/
X
X#include <sys/window.h>   /* Started with tam.h--too much trouble. */
X#include <sys/signal.h>
X#include <errno.h>
X
X#define uPC_HIGH_BIT    (0x8000)
X
Xtypedef unsigned short Scr_type;
Xtypedef unsigned char Scr_kluge;
X
X#define uPC_XMAX 720
X#define uPC_YMAX 300
X
X#define uPC_XSIZE       45 /* Short ints. */
X#define uPC_YSIZE uPC_YMAX
X
XScr_type uPC_display[uPC_YSIZE][uPC_XSIZE];
Xint uPC_width = 2*uPC_XSIZE;
Xint uPC_sx=0, uPC_sy=0;
Xint uPC_cur_linetype=0;
Xunsigned short uPC_raster_count=0;
X
X#define uPC_XLAST (uPC_XMAX - 1)
X#define uPC_YLAST (uPC_YMAX - 1)
X
X#define uPC_VCHAR 12
X#define uPC_HCHAR  9
X#define uPC_VTIC   8
X#define uPC_HTIC  12
X
Xextern errno, sys_nerr;
Xextern char *sys_errlist[];
X
Xstatic struct urdata uPC_ur = {(unsigned short *)uPC_display, 2*uPC_XSIZE, 0, 0,
X                           0, 0, 0, 0, uPC_XMAX, uPC_YMAX, SRCSRC, DSTOR, 0};
X
X#define IfErrOut(e1,e2,s1,s2) if (e1 e2) {\
Xfprintf(stderr, "%s:: %s %s\n", sys_errlist[errno], s1, s2);\
XuPC_fixwind(0);\
Xexit(-1);}
X
XuPC_init()
X{
X/* This routine will ioctl to change 0 size */
X   int i;
X   struct uwdata uw;
X   int uPC_fixwind();
X   short gw;
X
X/* Check that we are on the bitmapped window. */
X   if (iswind() != 0) {
X      fprintf (stderr, "Sorry--must run from the bitmapped terminal\n");
X      exit(-1);
X   }
X   for (i=1; i<=16; i++) {
X      if (i != SIGINT && i != SIGFPE)  /* Two are caught in plot.c */
X         signal (i, uPC_fixwind);
X   }
X
X/* Increase the screen size */
X   uw.uw_x = 0;
X   uw.uw_y = 0;   /* Leave room for top status line. */
X   uw.uw_width = uPC_XMAX;      /* 720 */
X   uw.uw_height = uPC_YMAX;     /* 288 normal--we clobber 12 (top row)*/
X   uw.uw_uflags = 1;         /* Creates with no border */
X
X   IfErrOut (ioctl(0, WIOCSETD, &uw), <0, "ioctl failed on", "WIOCSETD");
X}
X
X
XuPC_graphics()
X{
X/* This routine will clear the uPC_display buffer and window. */
X   register Scr_type *j;
X   register int i;
X
X   j = (Scr_type *)uPC_display;
X   i = uPC_YSIZE*uPC_XSIZE + 1;
X
X   while (--i)
X      *j++ = 0;
X
X   uPC_ur.ur_dstop = DSTSRC;   /* replace (clear screen). */
X   IfErrOut (ioctl(0, WIOCRASTOP, &uPC_ur), <0,
X      "ioctl failed", "WIOCRASTOP");
X   uPC_ur.ur_dstop = DSTOR;   /* Or in (show text) */
X}
X
X
XuPC_text()
X{
X/* This routine will flush the display. */
X
X   IfErrOut (ioctl(0, WIOCRASTOP, &uPC_ur), <0,
X      "ioctl failed", "WIOCRASTOP");
X/* Now position the cursor at the second to the last row--better later? */
X   wgoto (0, 24, 0);
X}
X
X
XuPC_linetype(linetype)
Xint linetype;
X{
X/* This routine records the current linetype. */
X   if (uPC_cur_linetype != linetype) {
X      uPC_raster_count = 0;
X      uPC_cur_linetype = linetype;
X   }
X}
X
X
XuPC_move(x,y)
Xunsigned int x,y;
X{
X/* This routine just records x and y in uPC_sx, uPC_sy */
X   uPC_sx = x;
X   uPC_sy = y;
X}
X
X
X/* Was just (*(a)|=(b)) */
X#define uPC_PLOT(a,b)   (uPC_cur_linetype != 0 ? uPC_plot_word (a,b) :\
X                                *(a)|=(b))
X
XuPC_plot_word(a,b)
XScr_type *a, b;
X/*
X   Weak attempt to make line styles.  The real problem is the aspect
X   ratio.  This routine is called only when a bit is to be turned on in
X   a horizontal word.  A better line style routine would know something
X   about the slope of the line around the current point (in order to
X   change weighting).
X
X   This yields 3 working linetypes plus a usable axis line type.
X*/
X{
X/* Various line types */
X   switch (uPC_cur_linetype) {
X   case -1:
X   /* Distinguish between horizontal and vertical axis. */
X      if (uPC_sx > uPC_XMAX/8 && uPC_sx < 7*uPC_XMAX/8) {
X      /* Fuzzy tolerance because we don't know exactly where the y axis is */
X         if (++uPC_raster_count % 2 == 0) *(a) |= b;
X      }
X      else {
X      /* Due to aspect ratio, take every other y pixel and every third x. */
X         *(a) |= (b & 0x9999);
X      }
X   break;
X   case 1:
X   case 5:
X   /* Make a |    |----|    |----| type of line. */
X      if ((1<<uPC_raster_count) & 0xF0F0) *(a) |= b;
X      if (++uPC_raster_count > 15) uPC_raster_count = 0;
X   break;
X   case 2:
X   case 6:
X   /* Make a |----|----|----|--- |    | type of line. */
X      if ((1<<uPC_raster_count) & 0x0EFFF) *(a) |= b;
X      if (++uPC_raster_count > 19) uPC_raster_count = 0;
X   break;
X   case 3:
X   case 7:
X   /* Make a | -  | -  | -  | -  | type of line. */
X      if ((1<<uPC_raster_count) & 0x4444) *(a) |= b;
X      if (++uPC_raster_count > 15) uPC_raster_count = 0;
X   break;
X   case 4:
X   case 8:
X   default:
X      *(a) |= b;
X   break;
X   }
X}
X
XuPC_vector(x,y)
Xunsigned int x,y;
X{
X/* This routine calls line with x,y */
X   int x1 = uPC_sx, y1=uPC_sy, x2 = x, y2 = y;
X   register int  c, e, dx, dy, width;
X   register Scr_type mask, *a;
X   static Scr_type lookup[] = {
X      0x0001, 0x0002, 0x0004, 0x0008,
X      0x0010, 0x0020, 0x0040, 0x0080,
X      0x0100, 0x0200, 0x0400, 0x0800,
X      0x1000, 0x2000, 0x4000, 0x8000,
X   };
X
X/* Record new sx, sy for next call to the vector routine. */
X   uPC_sx = x2;
X   uPC_sy = y2;
X
X   a = &uPC_display[(uPC_YSIZE - 1) - y1][x1 >> 4];
X   mask = lookup[x1 & 0x0f];
X   width = uPC_width;
X
X   if ((dx = x2 - x1) > 0) {
X      if ((dy = y2 - y1) > 0) {
X         if (dx > dy) {         /* dx > 0, dy > 0, dx > dy */
X            dy <<= 1;
X            e = dy - dx;
X            c = dx + 2;
X            dx <<= 1;
X
X            while (--c) {
X               uPC_PLOT(a, mask);
X               if (e >= 0) {
X                  (Scr_kluge *)a -= width;
X                  e -= dx;
X               }
X               if (mask & uPC_HIGH_BIT) {
X                  mask = 1;
X                  a++;
X               } else
X                  mask <<= 1;
X               e += dy;
X            }
X         } else {            /* dx > 0, dy > 0, dx <= dy */
X            dx <<= 1;
X            e = dx - dy;
X            c = dy + 2;
X            dy <<= 1;
X
X            while (--c) {
X               uPC_PLOT(a, mask);
X               if (e >= 0) {
X                  if (mask & uPC_HIGH_BIT) {
X                     mask = 1;
X                     a++;
X                  } else
X                     mask <<= 1;
X                  e -= dy;
X               }
X               (Scr_kluge *)a -= width;
X               e += dx;
X            }
X         }
X      } else {
X         dy = -dy;
X         if (dx > dy) {         /* dx > 0, dy <= 0, dx > dy */
X            dy <<= 1;
X            e = dy - dx;
X            c = dx + 2;
X            dx <<= 1;
X
X            while (--c) {
X               uPC_PLOT(a, mask);
X               if (e >= 0) {
X                  (Scr_kluge *)a += width;
X                  e -= dx;
X               }
X               if (mask & uPC_HIGH_BIT) {
X                  mask = 1;
X                  a++;
X               } else
X                  mask <<= 1;
X               e += dy;
X            }
X         } else {            /* dx > 0, dy <= 0, dx <= dy */
X            dx <<= 1;
X            e = dx - dy;
X            c = dy + 2;
X            dy <<= 1;
X
X            while (--c) {
X               uPC_PLOT(a, mask);
X               if (e >= 0) {
X                  if (mask & uPC_HIGH_BIT) {
X                     mask = 1;
X                     a++;
X                  } else
X                     mask <<= 1;
X                  e -= dy;
X               }
X               (Scr_kluge *)a += width;
X               e += dx;
X            }
X         }
X      }
X   } else {
X      dx = -dx;
X      if ((dy = y2 - y1) > 0) {
X         if (dx > dy) {         /* dx <= 0, dy > 0, dx > dy */
X            dy <<= 1;
X            e = dy - dx;
X            c = dx + 2;
X            dx <<= 1;
X
X            while (--c) {
X               uPC_PLOT(a, mask);
X               if (e >= 0) {
X                  (Scr_kluge *)a -= width;
X                  e -= dx;
X               }
X               if (mask & 1) {
X                  mask = uPC_HIGH_BIT;
X                  a--;
X               } else
X                  mask >>= 1;
X               e += dy;
X            }
X         } else {            /* dx <= 0, dy > 0, dx <= dy */
X            dx <<= 1;
X            e = dx - dy;
X            c = dy + 2;
X            dy <<= 1;
X
X            while (--c) {
X               uPC_PLOT(a, mask);
X               if (e >= 0) {
X                  if (mask & 1) {
X                     mask = uPC_HIGH_BIT;
X                     a--;
X                  } else
X                     mask >>= 1;
X                  e -= dy;
X               }
X               (Scr_kluge *)a -= width;
X               e += dx;
X            }
X         }
X      } else {
X         dy = -dy;
X         if (dx > dy) {         /* dx <= 0, dy <= 0, dx > dy */
X            dy <<= 1;
X            e = dy - dx;
X            c = dx + 2;
X            dx <<= 1;
X
X            while (--c) {
X               uPC_PLOT(a, mask);
X               if (e >= 0) {
X                  (Scr_kluge *)a += width;
X                  e -= dx;
X               }
X               if (mask & 1) {
X                  mask = uPC_HIGH_BIT;
X                  a--;
X               } else
X                  mask >>= 1;
X               e += dy;
X            }
X         } else {            /* dx <= 0, dy <= 0, dx <= dy */
X            dx <<= 1;
X            e = dx - dy;
X            c = dy + 2;
X            dy <<= 1;
X
X            while (--c) {
X               uPC_PLOT(a, mask);
X               if (e >= 0) {
X                  if (mask & 1) {
X                     mask = uPC_HIGH_BIT;
X                     a--;
X                  } else
X                     mask >>= 1;
X                  e -= dy;
X               }
X               (Scr_kluge *)a += width;
X               e += dx;
X            }
X         }
X      }
X   }
X}
X
X
XuPC_lrput_text(row,str)
Xunsigned int row;
Xchar str[];
X{
X   int col = 80-strlen(str), num, i;
X   struct utdata ut;
X   char *txt=ut.ut_text;
X
X/* Fill in the pad. */
X   for (i = 0; i < col; i++)
X      txt[i] = ' ';
X/* Then stick in the text. */
X   txt[i] = '\0';
X   strcat (txt, str);
X
X   if (row > 2)
X      puts (txt);
X   else {
X   /* This will fit on the 2 bottom "non-graphic" lines. */
X      switch (row) {
X      case 0: ut.ut_num =  WTXTSLK1; break;
X      case 1: ut.ut_num =  WTXTSLK2; break;
X      }
X      ioctl (0, WIOCSETTEXT, &ut);
X   }
X   wgoto (1, 24, 0);
X}
X
XuPC_ulput_text(row,str)
Xunsigned int row;
Xchar str[];
X{
X/* This routine puts the text in the upper left corner. */
X
X/* Just use the ANSI escape sequence CUP (iswind said that was ok!) */
X   printf ("\033[%d;%dH%s\033[25;1H", row+2, 2, str); /* +1 +2 ? */
X   fflush (stdout);
X}
X
X
XuPC_reset()
X{
X/* Reset window to normal size. */
X   uPC_fixwind (0);
X}
X
X
X
XuPC_fixwind(signo)
Xint signo;
X{
X   static struct uwdata wreset = { 0, 12, 720, 288, 0x1};
X   struct utdata ut;
X
X/* Reset the window to the right size. */
X   ioctl(0, WIOCSETD, &wreset);   /* 0, not wncur here! */
X
X/* Clear the lines affected by an _lrput_text. */
X   ut.ut_text[0] = '\0';
X   ut.ut_num =  WTXTSLK1;
X   ioctl(0, WIOCSETTEXT, &ut);
X   ut.ut_num =  WTXTSLK2;
X   ioctl(0, WIOCSETTEXT, &ut);
X/* Scroll the screen once. (avoids typing over the same line) */
X   fprintf (stderr, "\n");
X
X   if (signo) {
X      if (signo == SIGILL || signo == SIGTRAP || signo == SIGPWR)
X         signal (signo, SIG_DFL);
X      kill (0,signo);  /* Redo the signal (as if we never trapped it). */
X   }
X}
END_OF_FILE
if test 12181 -ne `wc -c <'./unixpc.trm'`; then
    echo shar: \"'./unixpc.trm'\" unpacked with wrong size!
fi
# end of './unixpc.trm'
fi
if test -f './util.c' -a "${1}" != "-c" ; then 
  echo shar: Will not clobber existing file \"'./util.c'\"
else
echo shar: Extracting \"'./util.c'\" \(8430 characters\)
sed "s/^X//" >'./util.c' <<'END_OF_FILE'
X/*
X *
X *    G N U P L O T  --  util.c
X *
X *  Copyright (C) 1986, 1987  Thomas Williams, Colin Kelley
X *
X *  You may use this code as you wish if credit is given and this message
X *  is retained.
X *
X *  Please e-mail any useful additions to vu-vlsi!plot so they may be
X *  included in later releases.
X *
X *  This file should be edited with 4-column tabs!  (:set ts=4 sw=4 in vi)
X */
X
X#include <ctype.h>
X#include <setjmp.h>
X#include <stdio.h>
X#include <errno.h>
X#include "plot.h"
X
Xextern BOOLEAN screen_ok;
X	/* TRUE if command just typed; becomes FALSE whenever we
X		send some other output to screen.  If FALSE, the command line
X		will be echoed to the screen before the ^ error message. */
X
Xchar *malloc();
X
X#ifndef vms
Xextern int errno, sys_nerr;
Xextern char *sys_errlist[];
X#endif /* vms */
X
Xextern char input_line[];
Xextern struct lexical_unit token[];
Xextern jmp_buf env;	/* from plot.c */
X
X
X/*
X * equals() compares string value of token number t_num with str[], and
X *   returns TRUE if they are identical.
X */
Xequals(t_num, str)
Xint t_num;
Xchar *str;
X{
Xregister int i;
X
X	if (!token[t_num].is_token)
X		return(FALSE);				/* must be a value--can't be equal */
X	for (i = 0; i < token[t_num].length; i++) {
X		if (input_line[token[t_num].start_index+i] != str[i])
X			return(FALSE);
X		}
X	/* now return TRUE if at end of str[], FALSE if not */
X	return(str[i] == '\0');
X}
X
X
X
X/*
X * almost_equals() compares string value of token number t_num with str[], and
X *   returns TRUE if they are identical up to the first $ in str[].
X */
Xalmost_equals(t_num, str)
Xint t_num;
Xchar *str;
X{
Xregister int i;
Xregister int after = 0;
Xregister start = token[t_num].start_index;
Xregister length = token[t_num].length;
X
X	if (!token[t_num].is_token)
X		return(FALSE);				/* must be a value--can't be equal */
X	for (i = 0; i < length + after; i++) {
X		if (str[i] != input_line[start + i]) {
X			if (str[i] != '$')
X				return(FALSE);
X			else {
X				after = 1;
X				start--;	/* back up token ptr */
X				}
X			}
X		}
X
X	/* i now beyond end of token string */
X
X	return(after || str[i] == '$' || str[i] == '\0');
X}
X
X
X
Xisstring(t_num)
Xint t_num;
X{
X	
X	return(token[t_num].is_token &&
X		   (input_line[token[t_num].start_index] == '\'' ||
X		   input_line[token[t_num].start_index] == '\"'));
X}
X
X
Xisnumber(t_num)
Xint t_num;
X{
X	return(!token[t_num].is_token);
X}
X
X
Xisletter(t_num)
Xint t_num;
X{
X	return(token[t_num].is_token &&
X			(isalpha(input_line[token[t_num].start_index])));
X}
X
X
X/*
X * is_definition() returns TRUE if the next tokens are of the form
X *   identifier =
X *		-or-
X *   identifier ( identifer ) =
X */
Xis_definition(t_num)
Xint t_num;
X{
X	return (isletter(t_num) &&
X			(equals(t_num+1,"=") ||			/* variable */
X			(equals(t_num+1,"(") &&		/* function */
X			 isletter(t_num+2)   &&
X			 equals(t_num+3,")") &&
X			 equals(t_num+4,"=") )
X		));
X}
X
X
X
X/*
X * copy_str() copies the string in token number t_num into str, appending
X *   a null.  No more than MAX_ID_LEN chars are copied.
X */
Xcopy_str(str, t_num)
Xchar str[];
Xint t_num;
X{
Xregister int i = 0;
Xregister int start = token[t_num].start_index;
Xregister int count;
X
X	if ((count = token[t_num].length) > MAX_ID_LEN)
X		count = MAX_ID_LEN;
X	do {
X		str[i++] = input_line[start++];
X		} while (i != count);
X	str[i] = '\0';
X}
X
X
X/*
X * quote_str() does the same thing as copy_str, except it ignores the
X *   quotes at both ends.  This seems redundant, but is done for
X *   efficency.
X */
Xquote_str(str, t_num)
Xchar str[];
Xint t_num;
X{
Xregister int i = 0;
Xregister int start = token[t_num].start_index + 1;
Xregister int count;
X
X	if ((count = token[t_num].length - 2) > MAX_ID_LEN)
X		count = MAX_ID_LEN;
X	do {
X		str[i++] = input_line[start++];
X		} while (i != count);
X	str[i] = '\0';
X}
X
X
X/*
X *	capture() copies into str[] the part of input_line[] which lies between
X *	the begining of token[start] and end of token[end].
X */
Xcapture(str,start,end)
Xchar str[];
Xint start,end;
X{
Xregister int i,e;
X
X	e = token[end].start_index + token[end].length;
X	for (i = token[start].start_index; i < e && input_line[i] != '\0'; i++)
X		*str++ = input_line[i];
X	*str = '\0';
X}
X
X
X/*
X *	m_capture() is similar to capture(), but it mallocs storage for the
X *  string.
X */
Xm_capture(str,start,end)
Xchar **str;
Xint start,end;
X{
Xregister int i,e;
Xregister char *s;
X
X	if (*str)		/* previous pointer to malloc'd memory there */
X		free(*str);
X	e = token[end].start_index + token[end].length;
X	if (*str = malloc((unsigned int)(e - token[start].start_index + 1))) {
X		s = *str;
X		for (i = token[start].start_index; i < e && input_line[i] != '\0'; i++)
X			*s++ = input_line[i];
X		*s = '\0';
X	}
X}
X
X
Xconvert(val_ptr, t_num)
Xstruct value *val_ptr;
Xint t_num;
X{
X	*val_ptr = token[t_num].l_val;
X}
X
X
X
Xdisp_value(fp,val)
XFILE *fp;
Xstruct value *val;
X{
X		switch(val->type) {
X			case INT:
X				fprintf(fp,"%d",val->v.int_val);
X				break;
X			case CMPLX:
X				if (val->v.cmplx_val.imag != 0.0 )
X					fprintf(fp,"{%g, %g}",
X						val->v.cmplx_val.real,val->v.cmplx_val.imag);
X				else
X					fprintf(fp,"%g", val->v.cmplx_val.real);
X				break;
X			default:
X				int_error("unknown type in disp_value()",NO_CARET);
X		}
X}
X
X
Xdouble
Xreal(val)		/* returns the real part of val */
Xstruct value *val;
X{
X	switch(val->type) {
X		case INT:
X			return((double) val->v.int_val);
X			break;
X		case CMPLX:
X			return(val->v.cmplx_val.real);
X	}
X	int_error("unknown type in real()",NO_CARET);
X	/* NOTREACHED */
X}
X
X
Xdouble
Ximag(val)		/* returns the imag part of val */
Xstruct value *val;
X{
X	switch(val->type) {
X		case INT:
X			return(0.0);
X			break;
X		case CMPLX:
X			return(val->v.cmplx_val.imag);
X	}
X	int_error("unknown type in real()",NO_CARET);
X	/* NOTREACHED */
X}
X
X
X
Xdouble
Xmagnitude(val)		/* returns the magnitude of val */
Xstruct value *val;
X{
X	double sqrt();
X
X	switch(val->type) {
X		case INT:
X			return((double) abs(val->v.int_val));
X			break;
X		case CMPLX:
X			return(sqrt(val->v.cmplx_val.real*
X				    val->v.cmplx_val.real +
X				    val->v.cmplx_val.imag*
X				    val->v.cmplx_val.imag));
X	}
X	int_error("unknown type in magnitude()",NO_CARET);
X	/* NOTREACHED */
X}
X
X
X
Xdouble
Xangle(val)		/* returns the angle of val */
Xstruct value *val;
X{
X	double atan2();
X
X	switch(val->type) {
X		case INT:
X			return((val->v.int_val > 0) ? 0.0 : Pi);
X			break;
X		case CMPLX:
X			if (val->v.cmplx_val.imag == 0.0) {
X				if (val->v.cmplx_val.real >= 0.0)
X					return(0.0);
X				else
X					return(Pi);
X			}
X			return(atan2(val->v.cmplx_val.imag,
X				     val->v.cmplx_val.real));
X	}
X	int_error("unknown type in angle()",NO_CARET);
X	/* NOTREACHED */
X}
X
X
Xstruct value *
Xcomplex(a,realpart,imagpart)
Xstruct value *a;
Xdouble realpart, imagpart;
X{
X	a->type = CMPLX;
X	a->v.cmplx_val.real = realpart;
X	a->v.cmplx_val.imag = imagpart;
X	return(a);
X}
X
X
Xstruct value *
Xinteger(a,i)
Xstruct value *a;
Xint i;
X{
X	a->type = INT;
X	a->v.int_val = i;
X	return(a);
X}
X
X
X
Xos_error(str,t_num)
Xchar str[];
Xint t_num;
X{
X#ifdef vms
Xstatic status[2] = {1, 0};		/* 1 is count of error msgs */
X#endif
X
Xregister int i;
X
X	/* reprint line if screen has been written to */
X
X	if (t_num != NO_CARET) {		/* put caret under error */
X		if (!screen_ok)
X			fprintf(stderr,"\n%s%s\n", PROMPT, input_line);
X
X		for (i = 0; i < sizeof(PROMPT) - 1; i++)
X			(void) putc(' ',stderr);
X		for (i = 0; i < token[t_num].start_index; i++) {
X			(void) putc((input_line[i] == '\t') ? '\t' : ' ',stderr);
X			}
X		(void) putc('^',stderr);
X		(void) putc('\n',stderr);
X	}
X
X	for (i = 0; i < sizeof(PROMPT) - 1; i++)
X		(void) putc(' ',stderr);
X	fprintf(stderr,"%s\n",str);
X
X	for (i = 0; i < sizeof(PROMPT) - 1; i++)
X		(void) putc(' ',stderr);
X#ifdef vms
X	status[1] = vaxc$errno;
X	sys$putmsg(status);
X	(void) putc('\n',stderr);
X#else
X	if (errno >= sys_nerr)
X		fprintf(stderr, "unknown errno %d\n\n", errno);
X	else
X		fprintf(stderr,"(%s)\n\n",sys_errlist[errno]);
X#endif
X
X	longjmp(env, TRUE);	/* bail out to command line */
X}
X
X
Xint_error(str,t_num)
Xchar str[];
Xint t_num;
X{
Xregister int i;
X
X	/* reprint line if screen has been written to */
X
X	if (t_num != NO_CARET) {		/* put caret under error */
X		if (!screen_ok)
X			fprintf(stderr,"\n%s%s\n", PROMPT, input_line);
X
X		for (i = 0; i < sizeof(PROMPT) - 1; i++)
X			(void) putc(' ',stderr);
X		for (i = 0; i < token[t_num].start_index; i++) {
X			(void) putc((input_line[i] == '\t') ? '\t' : ' ',stderr);
X			}
X		(void) putc('^',stderr);
X		(void) putc('\n',stderr);
X	}
X
X	for (i = 0; i < sizeof(PROMPT) - 1; i++)
X		(void) putc(' ',stderr);
X	fprintf(stderr,"%s\n\n",str);
X
X	longjmp(env, TRUE);	/* bail out to command line */
X}
END_OF_FILE
if test 8430 -ne `wc -c <'./util.c'`; then
    echo shar: \"'./util.c'\" unpacked with wrong size!
fi
# end of './util.c'
fi
echo shar: End of archive 4 \(of 7\).
cp /dev/null ark4isdone
MISSING=""
for I in 1 2 3 4 5 6 7 ; do
    if test ! -f ark${I}isdone ; then
	MISSING="${MISSING} ${I}"
    fi
done
if test "${MISSING}" = "" ; then
    echo You have unpacked all 7 archives.
    rm -f ark[1-9]isdone
else
    echo You still need to unpack the following archives:
    echo "        " ${MISSING}
fi
##  End of shell archive.
exit 0
-- 
	John Campbell               ...!arizona!naucse!jdc
                                    CAMPBELL@NAUVAX.bitnet
	unix?  Sure send me a dozen, all different colors.