SGLIB

 The Scientific Graphics Library (SGLIB) generates plots for devices
 that are compatible with the Tektronix 4014 or 4105 terminal classes.
 It is rather loosely based on the PLOT-10/Advanced Graphics package
 available from Tektronix, Inc.  The enhancements include sensible axis
 labeling, useful text display routines, error bars, true logarithmic
 data handling, terminal dependent screen switches, and 3-D isometric
 surface and contour plots.

 The last update to SGLIB was made in July, 2001.

 To use SGLIB:

     $ LINK YourProgram,USR:[PLOT]SGLIB_NOSHR/OPT   (non-shareable)
 or  $ LINK YourProgram,USR:[PLOT]SGLIB_SHR/OPT  (shareable)

 To link with newest version:
     $ LINK YourProgram, TRBIN:[TRANSP.OBJ.LIB]sglib/lib
 
Home Top


Introduction

 The PPPL Scientific Graphics library (SGLIB) is available on the VMS
 cluster, and various UNIX workstations including DEC, SUN, and HP.  The
 terminals and terminal emulators supported include:  Macintosh with
 Versaterm or VersatermPRO, the XTERM X-windows terminal emulator, and
 PPL's XTC 4014/4105 Tektronix emulator.  Plots can be output to a
 terminal only, to a disk file, or to a terminal with the option to save
 to a file on a page by page basis.  Plot files can be viewed on a
 terminal via the XPLOT program, or printed on a laser printer or the
 Tektronix color plotters.  The VGDS routines permits routing individual
 pages to remote devices.

 Some pointers on how to use the VMS Help utility:
 1)  To print the entire file:
 	$ HELP/OUT=SGLIB.HLP SG...
 	$ PRINT[/QUE=xxx] SGLIB.HLP
 2)  To see all the subtopics for a given topic, answer "*" at the prompt.
Home Top


Recent_changes

 Changes made in 2001:
 Option to convert tek to PS files.
 See Output

 Changes made in 2000:
 
 Fortran 90 Interfaces to handle REAL*8 data.
 See Precision_and_Real*8_Interface.
 
 Changes made in 1997:

 The XWDTH routine can now be used to allow more than 5 digits in the
 X-axis tick labels without generating a remote exponent.

Home Top


Precision_and_Real*8_Interface

 The sg library is written in default REAL precision.
 Routines described are coded for REAL*4 floating point arguments.
 To call a routine <name> instead with REAL*8 arguments, use R8_<name>.

 --or--

 fortran-90 codes can 

      use sglib_mod

 which defines all described routines as generic subroutine names.
 This means that if the compiler sees that the routine has REAL*4 arguments
 it will call the usual subroutine, but, if the compiler sees REAL*8 arguments,
 r8_<name> gets called.  The compiler can also check that all arguments are of
 the right type and all arrays of the correct rank.


 
Home Top


Linking

 To link with the shareable SGLIB, you must specify an option file (this
 is required by the VMS LINK command).  It is recommended that you
 always link using an option file:

 USR:[PLOT]SGLIB_NOSHR/OPT links to the standard non-shareable version
 USR:[PLOT]SGLIB_SHR/OPT links to the standard shareable version
 USR:[PLOT]SGNEW_NOSHR/OPT links to a pre-release of the next version
 USR:[PLOT]SGNEW_SHR/OPT links to the shareable version of SGNEW

 Examples (note switches):

 LINK prog,USR:[PLOT]SGLIB_SHR/OPT
 LINK prog,my_sgsubs,USR:[PLOT]SGLIB_NOSHR/OPT,[]my_lib/lib
 LINK/DEB prog,USR:[PLOT]SGNEW_NOSHR/OPT,[]my_lib/lib

 Other possibilities are:
 USR:[PLOT]SGLIB/LIB links to the non-shareable
 USR:[PLOT]SGLIB/OPT does the same thing as SGLIB_SHR/OPT
 USR:[PLOT]SGLIB_OLD.OLB/LIB links to the previous version of SGLIB

 If you link using SGLIB/LIB and call and VGDS routines, you should have
 done DEFINE LNK$LIBRARY VAXCRTL to resolve the C run-time references.

 If you have your own version of an SGLIB routine and link to the
 shareable version, you get a warning message from the linker.  If you
 call the routine directly from your program your version is used; if
 the routine is called by another SGLIB routine, SGLIB's version is
 used.
Home Top


MOREISD

 Due to a quirk of the VAX linker, when the total number of image
 sections in your program becomes greater than 96, your program's EXE
 file can balloon to a much larger size.  The EXE contains zeros for
 every word of uninitialized COMMON rather than just the size and a flag
 to zero memory when you run.  All the SG options files set this
 parameter to a high number.
Home Top


Logical_variables

 Many features of SGLIB can be controlled by logical variables set
 before the program executes.  Each of these is described elsewhere in
 this help file, but they are collected here for reference.
     PLOT              output device/file
     TERMINAL_TYPE     terminal; eg, V550, MAC, etc.
     TERMINAL_4105     YES for 4105 mode
                       NO or undefined for 4014
     TERMINAL_DASH     YES if hardware dashes and "point lines"
     TERMINAL_INPUT    device to be read for input
                       NONE for no input device
                       TT: for your "terminal" (e.g., DECterm window)
     TERMINAL_RES      4096 for 4096 resolution
     TERMINAL_TRAP     NO to disable broadcast trapping
     SG_DISK_BLOKS     n to set disk buffer to n blocks
     SG_TERM_BYTES     n to set terminal buffer to n bytes
     XPLOT$OUTPUT      output device/file for XPLOT

 Examples of definitions of PLOT:

 DEFINE PLOT FOO.PLT             output to file "FOO.PLT"
 DEAS PLOT                       output to SYS$OUTPUT
 DEFINE PLOT ",FOO.PLT"          output to screen and FOO.PLT
         keeps the frame if you type "D" to UPAUSE
 DEFINE PLOT XTC_MBX_0_username  output to XTC window
         where "username" is your user name
Home Top


UNIX

 SGLIB is available on all the UNIX platforms at PPPL, and has been
 exported to several other sites.  The library is named "libsg.a" in
 $NTCCHOME/lib, so you can link using:
         f90 foo.f -L${NTCCHOME}/lib -lsg -ljc -lportlib

 On SUNs you also need libsocket, so link:
         f90 foo.f  -L${NTCCHOME}/lib -lsg -ljc -lportlib -lsocket


 Note: If your code needs double precision, include Fortran 90 module
       sglib_mod.
	in fortran source: USE SGLIB_MOD
	compiler flags: -{I,M}${NTCCHOME}/mod

 The VMS logical variables are replaced by UNIX environment variables,
 e.g.:
         setenv TERMINAL_TYPE xterm
         setenv PLOT ',file.plt'
                output to screen and file "file.plt" 
                if you type "d" to upause beep
         setenv PLOT ',file.plt-ps'
                output to screen and PS file "file.plt_ps" 
                if you type "d" to upause beep
         setenv PLOT ',$WORK/file.plt'
         setenv PLOT XTC_MBX_0_username
         unsetenv PLOT
 The environment variables that are supported are:
     PLOT              output device/file
     TERMINAL_TYPE     terminal; eg, V550, MAC, etc.
     TERMINAL_4105     YES for 4105 mode
                       NO or undefined for 4014
     TERMINAL_DASH     YES if hardware dashes and "point lines"
     TERMINAL_INPUT    NONE for no input device
     TERMINAL_RES      4096 for 4096 resolution

 On UNIX systems, "TT" is NOT a synonym for your terminal; so you cannot
 use "setenv PLOT TT".  The UNIX version has all the same routines and
 calling sequences with the following exceptions:
     - UPAUSE must have an argument; change any instances of "CALL
     UPAUSE" to "CALL UPAUSE(1)"
     - RINITT must have a single argument; the optional status code is
     not allowed
     - the VGDS routines don't do anything.

 XPLOT is available to view plot files.  If you want to copy a file to
 another computer, send it in binary mode; e.g.:
     ftp> binary
     ftp> send name.plt

 XTC is available on all these systems.

Home Top


Sample_2D_plots

 This section contains several program fragments that illustrate the use
 of SGLIB routines to draw 2D plots.  Most of these examples assume the
 data is in two linear arrays; for other options see the Data_format
 topic.  You must call INITT to initiate a graphics sequence and FINITT
 to end graphics.  BINITT initializes all the common variables and
 UPAUSE waits at the end of the page for you to type a character.
Home Top


Simple_plot

 This program segment draws one curve, with grid, labeled ticks, and
 axis labels.
  
 	PARAMETER (NXY=20)
 	REAL X(NXY),Y(NXY)
 	...
 	CALL INITT(0)		!open terminal, switch to graph screen
 	CALL BINITT		!init plot options
 	CALL ERASE		!erase screen
 	CALL NPTS(NXY)		!set number of pts in X and Y
 	CALL CHECK(X,Y)		!determine axis params
 	CALL DSPLAY(X,Y)	!draw axes, ticks, and data curve
 	CALL AGTCHS('X axis')	!put centered label below X axis
 	CALL AGTCVS('Y axis')	!put centered label along Y axis
 	CALL UPAUSE(0)		!beep and wait
 	CALL FINITT(0,0)	!switch back to VT100 screen
Home Top


Modify_axes/ticks

 This program segment shows how to modify the appearance of the axes,
 tick marks, and tick labels, and select log scale:
  
 	PARAMETER (NXY=20)
 	REAL X(NXY)
 	CHARACTER TITLE*20,XLABEL*16,YLABEL*16
 	...
 	CALL INITT(0)		!open terminal, switch to graph screen
 	CALL BINITT		!init plot options
 	CALL ERASE		!erase the screen
 		!set screen window limits
 	CALL SLIMX(100,700)	!range is (0,1023), default is (150,900)
 	CALL SLIMY(100,700)	!range is (0,780),  default is (125,700)
 	CALL DLIMX(DXMIN,DXMAX)	!set data window limits
 	CALL DLIMY(DYMIN,DYMAX)	! (turns off auto-scaling)
 		!set axis "neatness", default=2
 	CALL XNEAT(0)		!0=extend endpoints to data,
 	CALL YNEAT(0)		! 1=to a minor tick, 2=to a major tick
 		!set form of major ticks, default=5, 0=no axis
 	CALL XFRM(6)		!1=no ticks, 2=ticks out, 3=ticks in
 	CALL YFRM(6)		! 4=ticks thru, 5=grid thru, 6=grid inside
 		!flag for linear or log scale, default=1
 	CALL XTYPE(1)		!1=linear, 2=log
 	CALL YTYPE(2)
 		!set tick label frequency, default=1
 	CALL XLAB(2)		!0=no label, 1=major ticks, 2=ends only
 	CALL YLAB(2)
  
 	CALL NPTS(NXY)	!number of points in X and Y
 	CALL CHECK(X,Y)
 	CALL DSPLAY(X,Y)	!draw axes, ticks, and data curve
 	CALL FRAME		!outline frame (all 4 axes lines)
 	CALL AGTCHS(XLABEL)	!put label below X axis
 	CALL AGTCVS(YLABEL)	!put label along Y axis
 	CALL AGTCGT(0,TITLE)	!put title above frame
 	CALL UPAUSE(0)		!beep and wait
 	CALL FINITT(0,0)	!switch back to VT100 screen
Home Top


Multiple_curves/line_types/symbols

 This program segment shows how to draw several curves within the same
 frame, each with a different line type and symbol:
  
 	PARAMETER (NXY=20)
 	REAL X(NXY,4),Y(NXY,4)
 	INTEGER LTYPE(4)  /0,1,2,3/
 	INTEGER LSYMB(4)  /2,4,6,8/
 	...
 	CALL INITT(0)		!open terminal, switch to graph screen
 	CALL BINITT		!init plot options
 	CALL ERASE		!erase the screen
 	CALL SLIMX(100,700)	!set screen window
 	CALL SLIMY(100,700)
 	CALL DLIMX(DXMIN,DXMAX)	!set data limits
 	CALL DLIMY(DYMIN,DYMAX)	! (min/max of all 4 curves)
 	CALL SIZES(1.24)	!scale factor for symbols
 	CALL STEPS(10)		!put symbol only every nth point
 	CALL NPTS(NXY)
 	CALL CHECK(X,Y)
 	CALL AGDSPL(X,Y)	!draw axes and ticks
 	DO I=1,4
 		!set line style, default=0
 	  CALL LINE(LTYPE(I))	!0=solid, 1=dots, 2=dotdash, 3=dash
 				! 4=long dash, 5-8=terminal dependent
 				! -1=nothing, -4=point, -5=marker(4105)
 		!set symbol, default=0
 	  CALL SYMBL(LSYMB(I))	!0=none, 1=circle, 2=X, 3=triangle
 				! 4=square, 5=star, 6=diamond, 7=bar
 				! 8=cross, 9=uparrow, 10=downarrow, 11=del
 	  CALL CPLOT(X(1,I),Y(1,I))	!draw curve
 	ENDDO
 	CALL AGTCHS(XLABEL)	!put label below X axis
 	CALL AGTCVS(YLABEL)	!put label along Y axis
 	CALL AGTCGT(0,TITLE)	!put title above frame
 	CALL UPAUSE(0)		!beep and wait
 	CALL FINITT(0,0)	!switch back to VT100 screen
 If the value of the argument to LINE is >= 10, it must be an integer of
 2 or 4 digits that defines a dash pattern; see Lines/Dashes topic.  To
 put an ASCII character as a symbol use:
 	CALL SYMBL(ICHAR('A'))	!put symbol A
Home Top


Dual_axes

 The default is to draw axis lines and tick marks on the left and bottom
 only; this program segment draws axes with ticks on the right and top
 also.
  
 	PARAMETER (NXY=20)
 	REAL X(NXY)
 	CHARACTER TITLE*20,XLABEL*16,YLABEL*16
 	...
 	CALL INITT(0)		!open terminal, switch to graph screen
 	CALL BINITT		!init plot options
 	CALL ERASE		!erase the screen
 	CALL SLIMX(100,700)	!set screen window limits
 	CALL SLIMY(100,700)
 	 <various parameter setting routines>
 	CALL NPTS(NXY)
 	CALL CHECK(X,Y)
 	CALL DSPLAY(X,Y)	!draw axes, ticks, and data curve
 	CALL AGTCHS(XLABEL)	!put label below X axis
 	CALL AGTCVS(YLABEL)	!put label along Y axis
 	CALL AGTCGT(0,TITLE)	!put title above frame
 	CALL XLOCTP(0)		!position to top,right of frame
 	CALL YLOCRT(0)
 	CALL XLAB(0)		!no tick labels
 	CALL YLAB(0)
 	CALL GRID		!draw axes, ticks for top, right
 	CALL UPAUSE(0)		!beep and wait
 	CALL FINITT(0,0)	!switch back to VT100 screen
Home Top


Color_(4105_only)

 If your program is generating 4105 mode output, you specify the color
 of curves, grid, and text with:
 	CALL AGCCURV(kolor)        !set color for curves
 	CALL AGCGRID(kolor)        !set color for grid/axes
 	CALL AGCTEXT(kolor)        !set color for labels/title
 where "kolor" is 0 for white (no line), 1 for black, 2 for red, 3 for
 green, 4 for blue, 5 for cyan, 6 for magenta, and 7 for yellow.  These
 should be called between BINITT and DSPLAY/CPLOT.  They set the color
 for curves, symbols, error bars, contours, and isometrics.  If these
 subroutines are executed in a program that is generating 4014 output,
 they are ignored.
Home Top


Isolated_lines_&_legends

 Not available yet.

 To position the cursor anywhere on the screen (including outside the
 graph window) and draw a symbol, e.g.  for a legend:
                             CALL MOVABS(IX,IY)
                             CALL SYMOUT(ISYM,SCALE)
Home Top


Error_bars

 This program segment draws a curve with error bars:
  
 	PARAMETER (NXY=20)
 	REAL X(NXY),Y(NXY),SIGMA(NXY)
 	...
 	CALL INITT(0)		!open terminal, switch to graph screen
 	CALL BINITT		!init plot options
 	CALL ERASE		!erase screen
 	CALL NPTS(NXY)		!set number of pts in X and Y
 	CALL LINE(-1)		!no line
 	CALL SYMBL(6)		!diamonds
 	CALL CHECK(X,Y)		!determine axis params
 	CALL DSPLAY(X,Y)	!draw axes, ticks, and data curve
 	CALL AGEYA(X,Y,SIGMA)	!error bars in Y
 	CALL AGTCGT(0,'Title')	!put title above frame
 	CALL UPAUSE(0)		!beep and wait
 	CALL FINITT(0,0)	!switch back to VT100 screen
Home Top


Data_formats

 Data arrays supplied as arguments to routines such as CHECK and CPLOT
 can be in one of 4 formats:

 a)  The data is in consecutive locations of a REAL*4 array.  To use
 this form, you must call NPTS to specify the number of points to use in
 each array:
 	PARAMETER (NXY=30)
 	REAL XAR(NXY),YAR(NXY)
 	...
 	DO I=1,NXY
 	  XAR(I+1) = I
 	  YAR(I+1) = MYFNC(I)
 	ENDDO
 	CALL BINITT
 	CALL NPTS(NXY)		!X and Y are non-standard
 	CALL CHECK(XAR,YAR)
 	CALL DSPLAY(XAR,YAR)
 If you call NPTS, both the X and Y arrays must be in this form.

 b)  Long form:  The first word of the REAL*4 array contains the number
 of points and the data is in the following consecutive locations:
 	PARAMETER (NXY=30+1)
 	REAL XAR(NXY),YAR(NXY)
 	...
 	XAR(1)=30.		!X and Y are long form
 	YAR(1)=30.		!number of points
 	DO I=2,NXY
 	  XAR(I) = I-1
 	  YAR(I) = MYFNC(I-1)
 	ENDDO
 	CALL BINITT
 	CALL CHECK(XAR,YAR)
 	CALL DSPLAY(XAR,YAR)
 If one of your arrays is in this form, the other can be type (c).

 c)  Short form:  The first word of the REAL*4 array is -1.; the second
 word is the number of data points, the third is the first value, the
 fourth is the increment.
 	PARAMETER (NY=30+1)
 	REAL XAR(4),YAR(NY)
 	...
 	XAR(1) = -1.		!X data is short form
 	XAR(2) = 30.		!number of points
 	XAR(3) = 1.		!start
 	XAR(4) = 1.		!delta
 	YAR(1) = 30.		!Y data is long form
 	DO I=2,NY
 	  YAR(I) = MYFNC(I-1)
 	ENDDO
 	CALL BINITT
 	CALL CHECK(XAR,YAR)
 	CALL DSPLAY(XAR,YAR)

 d)  Base X:  This is a short form for the X data when the Y data is
 non-standard.  The first word of the X array is the number of data
 points, the third is the first value, the fourth is the increment.
 	PARAMETER (NY=30+1)
 	REAL XAR(3),YAR(NY)
 	...
 	DO I=1,NY
 	  YAR(I) = MYFNC(I)
 	ENDDO
 	XAR(1) = 30.
 	XAR(2) = 1.		!start
 	XAR(3) = 1.		!delta
 	CALL BINITT
 	CALL AGBASX(1)		!X data is base-X form
 	CALL NPTS(30)
 	CALL CHECK(XAR,YAR)
 	CALL DSPLAY(XAR,YAR)
Home Top


Program_loops

 This section describes how to write programs that loop, generating
 multiple plots.  If you do not need to return to the alpha (VT100)
 screen or change output device(s), use:

 	CALL INITT(0)		!open terminal, switch to graphics
 	- loop from here -
 	CALL BINITT		!initialize frame (no output)
 	CALL ERASE
 	...
 	CALL UPAUSE(0)		!beep, wait for input, no erase
 	- down to here -
 	CALL FINITT(0,0)	!to alpha screen

 If you want screen switches between each page so you can do
 non-graphics dialog, use:

 	- loop from here -
 	- non-graphics I/O -
 	CALL INITT(0)		!open terminal, switch to graphics
 	CALL ERASE
 	CALL BINITT
 	...
 	CALL UPAUSE(0)		!beep, wait for input, no erase
 	CALL FINITT(0,0)	!to alpha screen
 	- down to here -

 If you want to do VT100 dialog in the middle of a plot page, use:

 	CALL INITT(0)		!open terminal, switch to graphics
 	CALL ERASE
 	CALL BINITT		!init frame
 	...
 	CALL UPAUSE(0)		!beep, wait for input, no erase
 	CALL AGSALF		!to alpha
 	- non-graphics I/O -
 	CALL AGSGRF		!to graphics
 	- more graphics -
 	CALL FINITT(0,0)	!to alpha screen

 If you are using RINITT, use:

 	Not available yet.


 If you are using VGDS, use:

 	- loop from here -
 	CALL AGVGDS(DEST_LIST)	!define output device(s)
 	CALL INITT(0)		!to graphics screen
 	CALL BINITT
 	...
 	CALL UPAUSE(0)		!beep, wait, input, no erase
 	CALL FINITT(0,0)	!to alpha screen
 	CALL AGVSEND(IERR)	!send page to destinations
 	- down to here -
Home Top


Subroutine_calls

 These lists contain most of the SGLIB routines you might want to call
 with their calling arguments.  Subtopics explain some of the more
 complicated routines.  To see how to order these in a program see the
 Using_2D_Routines topic.  The routines are in 3 sections, based on the
 "level" you are at; the lists are alphabetical within each section.
Home Top


INITT_to_FINITT

 These routines can be called anytime between INITT and FINITT.
 Locations given below as IX,IY are in screen coordinates (pixels) where
 0<=IX<=1023 and 0<IY<=780 unless you have set 4096 mode.
  
 INITT(KRASE)		!switch to Tek screen; erase if KRASE>0
  
 AGCTEXT(KOLOR)		!set color for subsequent text (see LINCLR)
 AGPNCLR(KOLOR)		!set panel color
 AGSALF			!switch to VT100 (alpha) screen
 AGSGRF			!switch to Tek (graph) screen
 AGTMHS(IX,IY,CSTR[,LEN])	!move to IX,IY and output string horizontal
 AGTMRS(IX,IY,IROT,CSTR,[,LEN])	!IROT: 0=horiz, 90=up, 270=down
 AGTMVS(IX,IY,CSTR[,LEN])	!move to IX,IY and output string vertical
 AGTHS(CSTR[,LEN])	!output character string horizontal
 AGTRS(IROT,CSTR,[,LEN]) !IROT: 0=horizontal, 90=up, 270=down
 AGTVS(CSTR[,LEN])	!output character string vertical
 ANMODE			!end vector sequence and call TSEND
 BEGPNL(IX,IY,IBOUND)	!begin panel at IX,IY (4105)
 BELL			!output a bell
 CHRSIZ(KSIZE)		!set char size: 1=default, 2=94%, 3=62%, 4=55%
 CSIZE(IHORZ,IVERT)	!return size of one character in pixels
 DSHABS(IX,IY,LINE)	!dash line to IX,IY
 DSHREL(IX,IY,LINE)	!dash line to cursor loc + IX,IY
 DRWABS(IX,IY)		!draw to IX,IY
 DRWREL(IX,IY)		!draw to cursor loc + IX,IY
 ENDPNL			!end panel (4105)
 ERASE			!clear the screen, start new page
 IAGHRES(IXY)		!(fnc) convert screen coord to 4096 resolution
 IAGLRES(IXY)		!(fnc) convert screen coord to 1024 resolution
 LINCLR(KOLOR)		!set line color
 	!0=black, 1=white, 2=red, 3=green, 4=blue, 6=magenta, 7=yellow
 LINWDT(NUMCHR)		!(fnc) return pixel width of NUMCHR chars
 LINHGT(NUMLIN)		!(fnc) return pixel height of NUMLIN lines
 MOVABS(IX,IY)		!move to IX,IY
 MOVREL(IX,IY)		!move to cursor loc + IX,IY
 NEWPAG			!clear the screen, start new page
 PLACE(LOC)		!set screen window limits to preset size
 	!1=STD, 2=UPH, 3=LOH, 4=UL4, 5=UR4, 6=LL4, 7=LR4,
 	!8=UL6, 9=UC6, 10=UR6, 11=LL6, 12=LC6, 13=LR6
 PNTABS(IX,IY)		!draw point at IX,IY
 PNTREL(IX,IY)		!draw point at cursor loc + IX,IY
 REVCOT(IX,IY,X,Y)	!convert screen location IX,IY to data point X,Y
 SCURSR(KCHAR,IX,IY)	!output crosshairs, read typed char and loc
 SEELOC(IX,IY)		!return current location
 SEEDW(XMIN,XMAX,YMIN,YMAX)	!return data min/max
 SEETW(MINX,MAXX,MINY,MAXY)	!return screen min/max
 SETCLP(IVALUE)		!0 to enable clipping, 1 to disable
 SETWIN			!substitute for CHECK in some cases
 SIZES(SYMSIZ)		!set symbol scale factor
 SLIMX(IXMIN,IXMAX)	!set window limits in screen units
 SLIMY(IYMIN,IYMAX)	!set window limits in screen units
 SYMOUT(ISYM,SCALE)	!ouput symbol ISYM at current location
 TERM(KDASH,KRES)	!KDASH=3 for hardware dashes, 2 for software
 		!KRES=1024 for normal screen, 4096 for high resolution
 TINPUT(KCHAR)		!input (integer*4) KCHAR
 TOUTPT(KCHAR)		!output (integer*4) KCHAR
 UPAUSE(KRASE,[KCHAR])	!wait for input, clear screen if KRASE>0
 			! if present, KCHAR=(integer*4) input
 VCURSR(KCHAR,X,Y)	!output crosshairs, read typed char and loc
 WINCOT(X,Y,IX,IY)	!convert data point X,Y to screen location IX,IY
  
 FINITT(0,0)		!switch to VT100 screen
Home Top


BINITT_to_CHECK

 These routines are called between BINITT and CHECK.  None of these
 routines do any output.  The list shows the routines that affect the X
 axis; for each there is a corresponding routine for the Y axis:
  
 BINITT			!init all parameters for CHECK/DSPLAY
  
 AGCCURV(KOLOR)		!set color for all CPLOT curves
 AGCGRID(KOLOR)		!set color for grid and ticks
 AGMNMX(ARRAY,AMIN,AMAX,NPTS,LLOG)	!for ARRAY of size NPTS,
 		!AMIN = min(ARRAY,AMIN), AMAX=max(ARRAY,AMAX)
 		!ignore values <=0 if LLOG=.TRUE.
 DINITX			!init X params
 DLIMX(DMIN,DMAX)	!set window limits in data units
 LINE(KLINE)		!line type for CPLOT
 HBARST(ISHADE,IWBAR,IDBAR)	!set line type to horizontal bars
 MNMX(ARRAY,AMIN,AMAX)	!AMIN = min(ARRAY,AMIN), AMAX=max(ARRAY,AMAX)
 NPTS(KPTS)		!number of points in XAR,YAR
 SLIMX(MINS,MAXS)	!set window limits in screen units
 SIZES(FACTOR)		!scale factor for symbols
 STEPL(KSTEPL)		!step between data points
 STEPS(KSTEPS)		!data point step between symbols
 SYMBL(KSYM)		!set symbol for CPLOT
 SYMOUT(KSYM,FACTOR)	!output any symbol at current location
 TEKSYM(KSYM,FACTOR)	!output Tektronix symbol (KSYM=1-11)
 VBARST(ISHADE,IWBAR,IDBAR)	!set line type to vertical bars
 XFRM(KFORM)		!tick form: 0=no axis or ticks, 1=no ticks
 		!2=ticks out, 3=ticks in, 4=ticks thru
 		!5=grid lines thru to ticks, 6=grid lines inside
 XLAB(KLABEL)		!tick labels: 0=none, 1=on major ticks
 		!2=on end ticks only
 XLEN(NPIX)		!length of major ticks
 XLOC(IX)		!set axis location to left edge + IX
 XLOCRT(IX)		!set axis location to right edge + IX
 YLOCTP(IY)		!set axis location to top edge + IX
 XMFRM(KFORM)		!form of minor ticks
 XMTCS(NMINX)		!set number of minor intervals
 XNEAT(KNEAT)		!tick neatness: 0=endpoints at data limits,
 		!1=extend to minor tick, 2=extend to major tick
 XTICS(NMAJOR)		!override auto tick intervals
 XTYPE(LINLOG)		!axis type: 1=linear, 2=log
 XWDTH(KWID)		!max number of chars in tick label
 		!if > 5, max chars with no remote exponent
 XZERO(KZERO)		!0=force axis to include 0, 1=don't
  
 CHECK(XARY,YARY)	!finish parameter setup
Home Top


CHECK_to_UPAUSE

 These routines must be called after CHECK:
  
 AGDSPL(XARY,YARY)	!draw axes, ticks
 AGEXA(XARY,YARY,SIGMA)	!draw horizontal error bars
 AGEYA(XARY,YARY,SIGMA)	!draw vertical error bars
 AGEXS(X,Y,SIGMA) 	!draw horizontal error at X,Y
 AGEYS(X,Y,SIGMA) 	!draw vertical error at X,Y
 AGEXSR(X,Y,SIGLO,SIGHI) 	!draw unequal length horiz error at X,Y
 AGEYSR(X,Y,SIGLO,SIGHI) 	!draw unequal vert error at X,Y
 AGTCGT(IY,CSTR,LEN)	!output string centered above frame
 AGTCHS(CSTR,LEN)	!output string centered below X axis
 AGTCVS(CSTR,LEN)	!output string centered beside Y axis
 BSYMS(X,Y,ISYM)	!draw symbol at location X,Y
 CPLOT(XARY,YARY)	!draw one curve
 DASHA(X,Y,LINE)	!dash line to X,Y
 DASHR(X,Y,LINE)	!dash line to current loc + X,Y
 DSPLAY(XARY,YARY)	!draw axes, ticks, and one curve
 DRAWA(X,Y)		!draw to X,Y
 DRAWR(X,Y)		!draw to current loc + X,Y
 FRAME			!draw frame (box) around screen window
 MOVEA(X,Y)		!move to X,Y
 MOVER(X,Y)		!move to current loc + X,Y
 POINTA(X,Y)		!draw point at X,Y
Home Top


Before_INITT

 These routines are called before INITT:
  
 AGVGDS			!set VGDS destination list
 RINITT(dest)		!set non-VGDS destination(s)
  
Home Top


text_routines

 The CSTR argument to the AGT (text) routines is a character variable;
 the LEN argument is optional.  The number of characters output is
 determined by:  (1) if LEN is present and non-zero, the length is LEN;
 (2) if CSTR has a '$', the length is the portion before the '$'; (3)
 otherwise it is the length of the character variable or constant.  On
 return the cursor is in position for the next character.  In the title
 routine, if IY=0, CSTR is output 15 screen units above the frame,
 otherwise CSTR is output at IY.

 The angle IROT must be 0 (horizontal), 90 (heading up), 180 (upside
 down), or 270 (heading down).
Home Top


INITT/FINITT

 INITT opens output device(s); for output to a terminal it switches the
 terminal to the graphics screen.  It outputs device initialization
 commands such as the character size, and the color map for 4105 mode.
 It also resets terminal related internal parameters.  If the argument
 is greater than zero, it erases the page.  The output stream(s) opened
 are:
 a)  if AGVGDS was called, output goes to the VGDS device(s)
 b)  if PLOT can be translated, output goes to those device(s)
 c)  output goes to SYS$OUTPUT

 FINITT switches back to the alpha (VT100) screen and dumps all output
 buffers.
Home Top


AGFCLOS/AGQFILE

 AGFCLOS(' ') closes any open plot disk file and deletes it if its
 length is less than 10 bytes, avoiding accumulation of "empty" files.
 AGFCLOS(filename), where "filename" is a character variable, closes the
 file and returns the full path name of the file.  If the file is empty,
 AGFCLOS returns blanks.

 AGQFILE(filename,jobname,note,quename,delete flag,error code) submits
 the file "filename" to the print queue "quename".  The flag (header)
 page on the QMS laser printer displays "jobname"; the flag page on the
 Telaris laser printer displays both "jobname" and "note".  If
 "delete flag" is .true., the file is deleted after it is printed.
 "error code" returns the VMS error from the submit (1=success).  To
 close the plot file and print it from within your program:

     CHARACTER PFILE*64
     CHARACTER CJOB*8 /'MY_JOB'/
     CHARACTER CNOTE*12 /'MY_NAME'/
       . . .
     CALL AGFCLOS(PFILE)
     CALL AGQFILE(PFILE,CJOB,CNOTE,'HL0',
     >  .FALSE.,IERR)!dont delete file
     IF (.NOT.IERR) THEN
     ..<handle error>
     ENDIF
Home Top


UPAUSE

 UPAUSE rings the bell and calls TINPUT which creates a pause until you
 type a character.
 a)  If the typed character is "C", it calls HDCOPY.
 b)  If there is an optional disk or VGDS file open, it keeps the frame
 in the file if the typed character matches your "keep" character or
 discards the frame if it doesn't match.
     CALL UPAUSE(KRASE)
     CALL UPAUCH(KCHAR)
 If the KRASE argument is omitted or has a value of 1, it erases the
 screen.  The UPAUCH routine returns the character typed while in UPAUSE
 as the low byte of the I*4 variable.
Home Top


AGFKEEP

 AGFKEEP is the routine that UPAUSE calls to keep or discard the present
 frame in an optional disk file.  When an optional file is open, each
 frame is written.  Thus AGFKEEP "keeps" the frame by doing nothing; it
 discards the frame by truncating the file back to the beginning of the
 frame.
     CALL AGFKEEP(ICHAR('x'))
 keeps the frame if the argument "x" matches the /KEEP character, or if
 it doesn't match the /NOKEEP character.  If you call AGFKEEP before
 calling UPAUSE, the AGFKEEP argument is used and what you type to
 UPAUSE is ignored.
Home Top


buffering

 SGLIB buffers output to provide faster execution times.  The buffer is
 dumped when you call FINITT, UPAUSE, ANMODE, TINPUT, or AGSALF.  If you
 need to flush the buffer at any other time, call one of these routines
 or call TSEND.
Home Top


Bar_routines

 You can draw horizontal and vertical bar charts.  To select bar chart
 format, somewhere between BINITT and DSPLAY/CPLOT:
     CALL HBARST(ISHADE,IWBAR,IDBAR)
               or
     CALL VBARST(ISHADE,IWBAR,IDBAR)
  
 where:
 	ISHADE	specifies the shading pattern; 0<=ISHADE<=15 (see below)
 	IWBAR	is the width of the bar in raster units;if 0,
 		uses default of 40
 	IDBAR	is the distance between the shading lines; if 0,
 		uses default of 20
  
 Values for ISHADE can be:
 	0	no pattern
 	1	horizontal lines
 	2	vertical lines
 	4	diagonal lines low to high
 	8	diagonal lines high to low
 Other values of ISHADE overlay these basic patterns.  For example,
 3=1+2 gives a square crosshatch; 12=4+8 gives a diagonal cross hatch.

 VBARST and HBARST call XFRM(0) and YFRM(0) to suppress drawing grid
 lines inside the graph window to avoid confusion, so if you want grid
 lines, call XFRM/YFRM after VBARST/HBARST.

 To draw a piece of a bar anywhere on the screen; e.g., for a legend:
     CALL FILBOX(IXMIN,IYMIN,IXMAX,IYMAX,ISHADE,LSPACE)
 where IXMIN/IYMIN/IXMAX/IYMAX define the rectangle in raster units,
 ISHADE is the shading type (as above) and LSPACE is the distance
 between shading lines in raster units (0 uses default).
Home Top


Error_bars

 The data format of the XARY, YARY, and SIGMA points is the same as for
 DSPLAY or CPLOT; you can call NPTS to set the length of the arrays, set
 the first element of the array to the number of points, or set the
 first element (of the X array) to -1 for short form.  Each error bar is
 drawn from X-SIGMA to X+SIGMA or Y-SIGMA to Y+SIGMA.  The increment
 between data points where error bars are drawn is set by STEPL.  Error
 bars are subject to clipping.  If you have called SYMB(ISYMB), a symbol
 is drawn at each X,Y point in addition to the error bar.
Home Top


Terminal_specifics

 Most of the terminals used at PPL (V550, MAC, VT240) have two separate
 displays:  a VT100 compatible alphanumerics screen and a Tektronix 4014
 and/or 4105 compatible graphics screen.  Special control sequences,
 which are slightly different for the different terminal types, are
 needed to switch from one screen to the other.  So that SGLIB can tell
 what kind of terminal you have, you must invoke the procedure
 @USR:[COM]TERMLOG either in your LOGIN.COM file or directly from your
 terminal, to set the logical variable TERMINAL_TYPE.
     $ @USR:[COM]TERMLOG     asks you for the terminal type
     $ @USR:[COM]TERMLOG xx  sets the type to "xx"
 You can check the value of TERMINAL_TYPE by the "SHOW LOGICAL
 TERMINAL_TYPE" command.  It should be one of the following:

         TERMINAL_TYPE terminal description
         ------------- --------------------

         TK4014        Tektronix 4014
         TK4107        Tektronix 4107
         V550          Visual 550, ModGraph
         MAC           Macintosh with Versaterm[PRO]
         VT240         DEC VT240
         XTERM         X-windows VT100/4014 emulator
         XTC           PPPL X-windows program to buffer, display, and print
                       Tektronix graphics
 The following routines generate screen switches:

         INITT         switch to graphics, among other things
         FINITT        switch to alpha, among other things
         AGSGRF        switch to graphics
         AGSALF        switch to alpha

 If you are outputting both to your terminal and a disk file, the
 control sequences are output only to the terminal.

 Not all terminals emulate the Tektronix 4014 in quite the same way.
 There are slight differences in the hardware dashes for dash line types
 1-4.  A Tektronix 4014 is supposed to have 4 characters sizes with 1
 the largest and 4 the smallest; however, the V550 and VT240 have only 2
 (sizes 1 and 2 are big, 3 and 4 are small), the ADM and Tektronix 4025
 have only 1.  Also the Tektronix 4025 does not support GIN input.  The
 V550 keyboard, including the Enter key, is disabled when the GIN
 crosshairs are showing.
Home Top


Versaterm/Pro

 If you are using a Macintosh with Versaterm or VersatermPRO, there are
 option settings that must be as described below for things to work
 properly.  For VersatermPRO:

 *-under the Settings menu, the Extras...  topic, the "Auto 4014 Entry"
 box must be checked.
 *-under the Emulation menu with "Tek 4014" selected, "Enabled Dialog"
 must be checked.
 *-under the Emulation menu with "Tek 4105" selected, "Enabled Dialog"
 must be checked.
 *-with "Tek 4014" selected under the Emulation menu, "Graphic Input"
 should have both "Mouse click" and "GIN terminator" set to "".  *-with
 "Tek 4014" selected, the first screen you get when with the Page
 Setup...  topic of the File menu should have "High Resolution Graphics"
 and "Chooser Print Driver"; if you are connected to a Laserwriter, the
 second Page Setup screen should have 25% reduction and landscape (man
 horizontal) orientation.

 For Versaterm: *-under the Settings menu, the Extras...  topic, the
 "Auto 4014 Entry" box must be checked.
 *-under the Emulation menu with "Tek 4014" selected, "Enabled Dialog"
 must be checked.  *-with "Tek 4014" selected under the Emulation menu,
 the first screen you get when with the Page Setup...  topic of the File
 menu should have "Chooser Print Driver"; if you are connected to a
 Laserwriter, the second Page Setup screen should have portrait (man
 vertical) orientation.
Home Top


ModGraph

 The changes that need to be made from the ModGraph power-on defaults
 are:
 *-Under the Display (keypad 2) menu, change "Screen Control" to "auto".
 *-Under the Graphics (keypad 4) menu, change "Status Terminator" to
 "CR-EOT".
Home Top


Output(logical PLOT, RINITT, AGVGDS)

 PPL extensions to SGLIB permit you to route plot output to your
 terminal, a disk file, both terminal and a file, or a VGDS device list.
 The precedence is:  (1) if the program calls AGVGDS, output is sent to
 that destination list; (2) if the program calls RINITT, output is sent
 to those device(s); (3) if you have defined logical variable PLOT
 before executing the program, output is sent there; (4) otherwise
 output is to SYS$OUTPUT, which is your terminal if you are running
 interactively.  A file must have extension .PLT if you want to print it
 on one of the laser printers.  A file containing 4105 output should
 have extension .4105; INITT changes the file extension from .PLT to
 .4105 if you are in 4105 mode.  You can call AGVGDS or RINITT at the
 beginning of each plot sequence to change the output destination if you
 want.

 When going to terminal and disk, or to VGDS, you can select which
 screens are saved and which are discarded.  If your output is defined
 (via logical PLOT or RINITT) to be both your terminal and a disk file,
 the program must call UPAUSE at the end of each frame to determine, on
 the basis of the character typed at the UPAUSE wait, whether to "send"
 the frame to the disk file or not.  The /KEEP (/NOKEEP) switch on the
 file name specifies what character is cause a frame to be saved or not
 saved.  Alternately the program can call AGFKEEP to simulate the user
 typing a character.

 Examples:

 DEFINE PLOT FOO.PLT             output to file "FOO.PLT"
 ASSIGN FOO.PLT PLOT:            same
 DEAS PLOT                       output to SYS$OUTPUT
 DEFINE PLOT ",FOO.PLT"          output to screen and FOO.PLT
         keeps the frame only if you type  D  to UPAUSE
         i.e., /KEEP=D
 DEFINE PLOT "FOO.PLT,"          same
 DEFINE PLOT "FOO.PLT/PS,"       output to screen and
                                 post script file FOO.PS
 DEFINE PLOT ",FOO.PLT/KEEP=x"   output to screen and FOO.PLT
         keeps the frame only if you type "x" to UPAUSE
 DEFINE PLOT ",FOO.PLT/NOKEEP=x"
         keeps the frame unless you type "x" to UPAUSE
 DEFINE PLOT ",FOO.PLT/KEEP"
         keeps the fram only if you type CR
 DEFINE PLOT ",FOO.PLT/NOKEEP"
         keeps the frame unless you type CR

 Unix Syntax:
 substitute "/" with "-"
 e.g. setenv PLOT "foo.plt-ps,"

Home Top


RINITT

 RINITT changes the output destination; it should be called before
 INITT.  (RINITT defines the output stream(s), but INITT actually opens
 them.)
         CALL RINITT(destination)
 The "destination" is a character string with a file specification or a
 logical variable; "TT" is your terminal.  If you specify the same file
 name in successive RINITT calls, a new version of the file is created.
Home Top


AGVGDS

 The AGVGDS/AGVSEND subroutines let you send individual plot frames to
 the display screens in the TFTR/PBX control rooms, the laser printers,
 disk files, and/or your own terminal, from an SGLIB program.  You call
 AGVGDS to provide a destination list containing one or more of these
 devices.  If the list has any devices other than your terminal, SGLIB
 creates a temporary file to hold the plot.  AGVSEND "sends" the frame
 by copying the temporary file to your disk file, queueing it to your
 printer, and/or queueing it to the VGDS server for a control room
 display screen.

 In addition to returning a status code to your program, the VGDS
 routines output a one-line message to SYS$OUTPUT (your terminal or log
 file) for any error condition.  For frames sent to a display screen or
 printer, a message is also output if the frame is successfully queued:
         Queued to xxx           frame sent to printer
         Entry nn                frame sent to VGDS server

 The Subroutines subtopic describes the subroutines and their arguments,
 and shows sample program segments.  Destinations describes the devices
 and switches in a destination list, and the use of logical variables.
 The Errors subtopic lists various error conditions you might encounter.
 For more information on the VGDS utilities and server, see HELP VGDS.
Home Top


Subroutines

 The following program segment shows the use of the VGDS routines for a
 batch job that would use logical variables to define the output
 devices:
                               !declarations
       CHARACTER*32 DNAME      !for device name from AGVERR
       CHARACTER*72 ETEXT      !for SYS$GETMSG
       	...
                               !start of plot
                               !DEST_LIST is defined outside the program
       CALL AGVGDS ('DEST_LIST', NGOOD)
       IF (NGOOD.EQ.0)  <bypass all plot code>
  
       CALL INITT(240)         !generate screen clear (non-0 arg)
       	...
                               !end of frame
       CALL UPAUSE(0)          !0 suppresses screen clear
       CALL FINITT(0,0)        !do screen switch to VT100
       CALL AGVSEND(IERR)      !send frame to device list
       IF (.NOT.IERR) THEN
                               !have at least one error, find out more
         IDNO = 1
         NDEVS = 1
         DO WHILE (IDNO.LE.NDEVS)
                               	!get individual device name, type, status
           CALL AGVERR(IDNO, NDEVS, DNAME, ITYPE, IDERR)
           IF (DNAME.NE.' ' .AND. (.NOT.IDERR)) THEN
                               	!if error, output info to sys$output
             WRITE(*,'(2X,A,I2,A)') 'Device type ',ITYPE,' for '//DNAME
             CALL SYS$GETMSG(%VAL(IDERR),LTEXT,ETEXT,,)
             WRITE(*,'(2X,A)') ETEXT(1:LTEXT)
           ENDIF
           IDNO = IDNO+1
         ENDDO
       ENDIF

 AGVGDS is called before INITT.  It has either 1 or 2 arguments.  The
 first is required; it is a character constant or variable that supplies
 the destination list.  The string can contain the device list or a
 logical variable that translates to the list.  The completely
 translated list can specify up to 6 devices.  (See the Destinations
 subtopic for more about the destination list.)  If the string is blank
 (or translates to a blank), SGLIB acts as if AGVGDS had not been called
 and uses logical variable PLOT or SYS$OUTPUT to determine the output
 device(s).

 The second argument is optional; it is an integer variable that returns
 the number of devices in the list that have no initial error condition
 and are not the null device.  This allows batch jobs that set a logical
 variable to NL: to "turn off" plot output to bypass the entire graphics
 sequence.  AGVGDS does as much checking about the devices as possible.
 If it finds an error, it outputs a message (obtained from SYS$GETMSG)
 to your terminal or log file, and saves the error code to return to
 your program via AGVERR.  If there is at least one valid device that is
 a disk file, printer, or display screen, AGVGDS creates a temporary
 file in VGDS_SCRATCH (a system logical) so that the plot you generate
 is stored in this file.

 Examples of calls to AGVGDS:
   (1)	DESTS = 'ES10,RL0'
 	CALL AGVGDS (DESTS)
  
   (2)	CALL AGVGDS ('PLOT_TO', NGOOD)
 		where outside your program you have defined
 	$DEFINE PLOT_TO MYPRINTER,MYSCREEN
 	$DEFINE MYPRINTER RL0
 	$DEFINE MYSCREEN ES10

 AGVSEND is called after FINITT.  It "sends" the frame to each valid
 device in the list.  The integer argument returns a status code that is
 1 (SS$_NORMAL) if output to all devices was successful; otherwise it is
 the status code for the last device that had an error.  As with any VMS
 status code in a Fortran program, although it is an integer variable
 you can treat it as either integer or logical.  Fortran variables are
 TRUE if they are odd (low order bit set), and FALSE if they are even.
 All VMS system services return an odd status code for success, and an
 even value for failure.

 For output to a display screen, AGVSEND "queues" the temporary file to
 the VGDS server on the node that "owns" the screen; the server outputs
 the plot frame to the screen and deletes the temporary file when it is
 no longer needed.  While the frame is showing on the display screen,
 you can obtain a copy on a printer, on your terminal, or to a disk file
 (See HELP VGDS).  For output to a printer, AGVSEND queues the temporary
 file to the printer with the "delete when printed" switch.  For output
 to a disk file, AGVSEND copies the temporary file to the specified file
 name.  If you specify append mode (/APP) and the file already exists,
 the frame is appended; otherwise a new file is created.

 The AGVERR subroutine can be called after AGVSEND to get more
 information about the destination list and the error associated with
 each device.  Its input arguments are the device number, IDNO (1-6);
 its outputs are the total number of devices, the actual name for device
 number IDNO after all translations, its device type, and the VMS status
 code.  The device types are:  0 = invalid; 1 = disk file; 2 = terminal;
 3 = printer queue; 4 = display screen; 5 = null device.

 INITT generates both a screen initialization sequence (resets the
 character size, etc.) and a screen clear.  You could achieve the same
 thing by calling INITT(0), then ERASE or NEWPAG.  If you want to send
 the frame to a VGDS display screen, which is a dumb terminal, you must
 be careful to have the screen clear/initialize at the beginning, and
 not call ERASE or NEWPAG before the end of the frame.
Home Top


Destinations

 You provide the destination device(s) via a character argument to
 subroutine AGVGDS.  This is a text string specifying devices, and/or
 logical names that translate to devices, separated by commas.  Possible
 destinations are:

   FIDDLE.PLT	disk file "fiddle.plt"; the default directory is where you
 		are running the program; each frame creates a new version
   FID.PLT/APP	disk file "fid.plt"; each new frame appended to the file;
 		a new file is created if none exists
   HS04		display screen HS04 in the TFTR control room
   DL0		the DL0 laser printer
   SYS$OUTPUT	your terminal for interactive jobs; undefined for batch
   TT		your terminal for interactive jobs; null device for batch
  
 The display screens in the TFTR control room have (logical) names HS00
 through HS16.  The PBX control room screens are ES01 through ES20.  You
 can send to any printer queue that you can PRINT to.  Frames sent to a
 printer have a flag page with your name, and a file name of xxx.PLT
 (where "xxx" is your job's process id number in hexadecimal).

 There are two switches that apply to output devices:
       /APP                    set append mode (disk files only)
       /KEEP=x                 set keep character to "x"
 When you execute your program interactively, the /KEEP switch causes
 the plot to be displayed on your terminal as it is generated.  The
 frame is sent to the device only if the character you type at the
 UPAUSE beep matches the keep character.  For example, /KEEP=D sets the
 keep character to "D".  Every time you type "D" or "d" to UPAUSE, the
 frame is sent; when you type any other character it is not sent.  If
 you use /KEEP (no "=x"), the keep character is CR (carriage return).
 /NOKEEP=x sends the frame if you type anything except "x".  The
 character match is case insensitive (k is the same as K).  If a batch
 job uses this switch, the frame is always sent for /KEEP=x and never
 sent for /NOKEEP=x.

 AGVGDS does a multi-level, multi-index, translation of the character
 string.  This means it translates each (comma separated) piece of the
 string repetitively.  If you do CALL AGVGDS('VGDS',NGOOD), the
 following definitions would both result is a destination list of ES10
 and RL0:
   (1)	$ DEFINE VGDS ES10,RL0
  
   (2)	$ DEFINE VGDS MYPRINTER,MYSCREEN
 	$ DEFINE MYPRINTER RL0
 	$ DEFINE MYSCREEN ES10
Home Top


Errors

 The errors you can get from the VGDS routines include:

   %RMS-F-FNM, error in file name
     The name of the output plot file is invalid.

   %SYSTEM-F-TOOMANYLNAM, logical name translation exceeded allowed
     depth
     A logical variable is probably defined recursively ($DEFINE ABC XYZ
     and $DEFINE XYZ ABC).

   %RMS-F-SYN, file specification syntax error
     This is really a catch-all error.  AGVGDS couldn't figure out what
     the device is.

   %SYSTEM-F-NOTFILEDEV, device is not file structured
     The device is not supported; e.g., a terminal that is not your own.

   %SYSTEM-F-NOSUCHOBJ, network object is unknown at remote node
     A device that includes a node specification is not supported.

   %SYSTEM-W-NOSUCHDEV, no such device available
     Most likely, this is an invalid disk in a file specification.

   %RMS-E-PRV, insufficient privilege or file protection violation
     A disk file specifies a directory that you can't write to.

   %FOR-F-INCRECTYP, inconsistent record type
     A disk file in append mode is not a plot file.

   %RMS-E-CRE, ACP file create failed
     An output plot file has an invalid node specification.

   %VGDS-E-OFFLINE, Device is offline and unavailable
     The display screen has a hardware problem and has been set offline.
     You get both the "Entry nn" message and the error message from
     AGVSEND to your terminal or log file.

 For a description of all possible errors from the routine that
 communicates with the VGDS server see HELP VGDS CONDITION_CODES.
Home Top


Efficiency

 The basic curve drawing routine CPLOT is the "fast" version developed
 at PPL.  When consecutive Y values evaluate to the same Y screen
 coordinate, a single line is drawn connecting the first to the last
 rather than individual lines connecting each pair of points.  The
 "fast" algorithm is used ONLY when there are no symbols and you are
 drawing a solid line (not dashed or dotted).  Execution is even faster
 with no clipping (CALL AGNCLP).  With clipping on, only the portion of
 any vector that is within your data/screen window is plotted.
 	CALL AGNCLP	!plot data outside window
 	CALL AGCLIP	!clip data outside window
 With clipping off, any coordinate that goes "off the screen" is set the
 physical screen limit, which can misrepresent data.
Home Top


Input(TINPUT,SCURSR,VCURSR)

 TINPUT reads one character from logical device SYS$COMMAND.
 SYS$COMMAND is the batch control file for a batch job or a .COM file,
 or your terminal if you are running interactively.  If TINPUT gets an
 end-of-file error while reading from a disk file, it assumes an input
 character of one blank.

 If you want to run from a command file, and have TINPUT read from the
 file rather than your terminal, use
 	ASSIGN/USER SYS$INPUT SYS$COMMAND

 The routines to read the cursor location on the screen (GIN mode input)
 are:

 	CALL SCURSR(ICH,IX,IY)	!read cursor location and input character
 	CALL VCURSR(ICH,X,Y)	!read virtual cursor and input character
  
 	CALL AGSCUR(CCH,IX,IY)	!read cursor location and input character
 	CALL AGVCUR(CCH,X,Y)	!read virtual cursor and input character
  
 where:
 	IX,IY	are X,Y coordinates of cursor in screen units
 	X,Y	are X,Y coordinates of cursor in virtual units
 	ICH	is typed character as an integer
 	CCH	is typed character as a character
 The type-ahead buffer is purged by the get-cursor routines before
 TINPUT is called.
Home Top


Lines/Dashes/Symbols/Colors

 This is a quick reference of the integer codes for the line, symbol,
 and color routines.

 The argument to subroutine LINE sets the line (dash) type to be used
 for subsequent curves.  The dash patterns can be created by the SGLIB
 software or by the physical output device depending on the setting of
 logical variable TERMINAL_DASH.  For software generated line patterns:

         VALUE     MEANING
         -----     -------
         -5        put a marker at each data point (4105 mode)
         -4        put a point at each data point
         -1        no line (move only)
         0         solid line
         1         dots
         2         dot dash
         3         dashes
         4         long dashes
         5-7       dots
         >10       software dash


 You can output a symbol at every point or every nth point of a line.
 The symbol codes are:
                   4014            41xx
                   ----            ----
         0         no symbol       dot
         1         circle          small plus
         2         X               larger plus
         3         triangle
         4         square          circle
         5         star            X
         6         diamond         square
         7         vertical bar
         8         cross
         9         up arrow
         10        down arrow
         11        del
         12        circle          MacCircle
         13        circle with plus inside
         14        square with X inside
         15        diamond with plus inside
         33-127    ASCII character (33=A)
  
 To scale the symbol to size
         CALL SIZES(SCALE)
 where SCALE=1. is the default; SCALE>1. makes it bigger.
  
 To draw a symbol only every nth point
         CALL STEPS(ISTEP)
         CALL AGSTEPS(ISTEP,ISTART)
 where ISTEP=number of data points between symbols, ISTART=offset to first
 symbol.

 A software dash pattern is an integer of 2 or 4 digits where each
 (decimal) digit is interpreted as:

         VALUE     MEANING
         -----     -------
         1         draw line for 5 raster units
         2         move 5 raster units
         3         draw line for 10 raster units
         4         move 10 raster units
         5         draw line for 25 raster units
         6         move 25 raster units
         7         draw line for 50 raster units
         8         move 50 raster units

 For example, CALL LINE(3454) would create a line pattern with:  10
 units visible, 10 units blank, 25 units visible, 10 units blank.  Each
 curve drawn after this call would consist of lines of this pattern.


 You can specify that dash line types 1-7 be either hardware or software
 generated, by setting logical name TERMINAL_DASH.  For hardware
 generated lines, SGLIB outputs a line type code, then draws a solid
 line; the output device must know how to interpret the code to draw
 this as a dashed (or color) line.  The QMS laser printer does a poor
 job of generating dashed lines.

 To enable hardware dash lines:
 	DEFINE TERMINAL_DASH YES
 To turn this off:
 	DEAS TERMINAL_DASH

 This is what you get from various "devices" for hardware dash patterns
 1-7:

         code    laser/V550  Mac line    Mac color
         ----    ----------  --------    ---------
         1       dots        dots        green
         2       dot-dash    dash        red
         3       dash        long dots   yellow
         4       long dash   long dash   blue
         5       solid       space dot   cyan
         6       solid       dot dash    magenta
         7       solid       solid       black

 If you want the colors to be in the same order as the 4014 table in
 VersatermPro, order the table numbers as:  7,2,1,4,5,6,3.  The line
 type does not affect the axes or symbols; these are always solid black.

 When a marker line is selected (LINE(-5) in 41xx mode), the marker type
 is set by calling SYMBL.
Home Top


Halts

 Because we have retained the original calling sequences of the PLOT-10
 routines, which have no provision for error returns, there is a
 question of what to do upon encountering error conditions in SGLIB.
 The current philosophy is to halt the program (with an error message
 followed by a Fortran STOP) if certain errors occur.  The following
 list gives various error situations and what the library does for each:

 *-INITT/TOUTPT now halt with a VMS system error message if disk output
 has been selected and the file cannot be opened; the most usual error
 conditions are disk over quota or no privilege (you have set default to
 an area where you do not have write privelege).

 *-BINITT now halts with an error message INITT NOT CALLED if the TCS
 common block is not initialized

 *-CHECK/DSPLAY now halt with the error message BINITT NOT CALLED if the
 AG common block is not initialized
Home Top


Isometric(3D)_plots

 The isometric routines draw a 3-D surface with grid lines, tick lines
 and labels, and axes labels.  They were written at PPPL, using the
 hidden line algorithm from the NCAR SRFACE routines.  AGISOM is the
 more commonly used routine; it can draw the surface with or without
 hidden line removal; as viewed from top, bottom, or both; with linear
 or logarithmic data.  AGISOC has the same options, but can also draw Z
 contour lines.
Home Top


AGISOM_Example

 Sample program:
 	PARAMETER (NXDIM=50)    !X dimension of Z array
 	PARAMETER (NYDIM=30)	!Y dimension of Z array
 	REAL X(NXDIM)		!X points at which Z(X,Y) is defined
 	REAL Y(NYDIM)		!Y points at which Z(X,Y) is defined
 	REAL Z(NXDIM,NYDIM)	!surface data
 	CHARACTER*20 XLABEL	!label for X axis
 	CHARACTER*20 YLABEL	!label for Y axis
 	CHARACTER*20 ZLABEL	!label for Z axis
  
 	<read/calculate X, Y, Z data values>
 	XLABEL='NEUTRON ENERGY (MEV)'
 	YLABEL='GAMMA ENERGY (MEV)'
 	ZLABEL='CROSS SECTION (1/CM)'
  
 C  initialization
 	CALL INITT(0)		!switch from VT100 to graphic
 	CALL ERASE		!clear the screen
 	CALL AGINIT		!init AGISOM options
 C  change various options from the defaults
 	CALL AGIZTY(2)		!Z type - 1 for linear, 2 for log
 	CALL AGIXNT(0)		!extend axes to actual data limits
 	CALL AGIYNT(0)
 	CALL AGIZNT(0)
 	CALL AGIHID(.TRUE.)	!remove hidden lines
 	CALL AGISID(1)		!1=upper side only, -1=lower side, 0=both
 C  generate the plot
 	NX = 46			!number of valid X points
 	NY = 21			!number of valid Y points
 	CALL AGISOM(X,Y,Z,NXDIM,NX,NY,XLABEL,YLABEL,ZLABEL)
 	CALL UPAUSE(0)		!beep and pause
 	CALL FINITT(0,0)	!switch from graphics to VT100
 There are more option changing routines, which are described under
 Routine_Arguments.
Home Top


Routine arguments

 The call to AGISOM is:
 	CALL AGISOM(X,Y,Z,NXDIM,NX,NY,XLABEL,YLABEL,ZLABEL)
 where:
  X            (1-D real array) X data
  Y            (1-D real array) Y data
  Z            (2-D real array) Z(X,Y) data
  NXDIM        (integer) X dimension of Z array
  NX           (integer) number of X points to plot
  NY           (integer) number of Y points to plot
  XLABEL       (character) X axis label
  YLABEL       (character) Y axis label
  ZLABEL       (character) Z axis label

 To draw a surface with Z contours:

 	CALL AGISZC(NC,C)	!set the contour levels to be drawn
 				!draw surface with Z contours
 	CALL AGISOC(X,Y,Z,NXDIM,NX,NY,XLABEL,YLABEL,ZLABEL,WORK)
  
 where:
  NC           (integer) number of contours (<= 41)
    =0         no contours are drawn
    =-1        contours drawn at major ticks
    =-2        contours drawn at major and minor ticks
    <-2        IABS(NC) contours drawn at values evenly spaced from C(1) to C(2)
    >0         NC contours set in C by the user
  C            (1-D real array) contour test values
  WORK         (1-D real array) work space of dimension at least 2*NX*NY

 The routines to modify an isometric plot must be called after AGINIT
 and before AGISOM or AGISOC.  The AGIDLx routines may be used to force
 a data window to span a greater range than normal.  Since the data is
 not clipped, it is not advisable to set limits less than the actual
 data limits.

 set data limits (similar to DLIMX/Y)
   CALL AGIDLX(XMIN,XMAX)
   CALL AGIDLY(YMIN,YMAX)
   CALL AGIDLZ(ZMIN,ZMAX)
  
 set screen limits (similar to SLIMX/Y)
   CALL AGISLX(MINX,MAXX)	!default = 150,590
   CALL AGISLY(THETA,LENGY)	!default = 45.,440
   CALL AGISLZ(MINZ,MAXZ)	!default = 120,465
  
   where:
   THETA   (real) is angle in degrees from the X axis.  It must be in
       the first two quadrants and not too near 0, 90, or 180.
   LENGY   (integer) is the Y axis length in screen units.  and the y
       axis length in screen units.  If you set LENGY=0, the routine
       calculates a value for you based on the length of the X axis and
       THETA.
  
 set type of transformation
   CALL AGIXTY(IVALUE)	!1 for linear, 2 for logarithmic
   CALL AGIYTY(IVALUE)	! default = 1
   CALL AGIZTY(IVALUE)
  
 set axis rounding option
   CALL AGIXNT(NEAT)	!0 for raw data endpoints,
   CALL AGIYNT(NEAT)	!1 to round to minor ticks,
   CALL AGIZNT(NEAT)	!2 to round to major ticks
 			!default = 2
  
 set increment between data curves
   CALL AGISTX(NX)	!plot z vs y every NXth x
   CALL AGISTY(NY)	!plot z vs x every NYth y
 			!default = 1
  
 draw reference lines to the X/Y axes
   CALL AGISKT(T,T)	!draw a line from z(x,y) to the x,y
 			! plane at the respective axis
 			!defaults are .FALSE.
  
 set to clip out of range Z values
   CALL AGIZCL(.TRUE.)	!plot out of range data at the rational
 			! limit of the z axis
 			!default is .TRUE.
  
 draw surface with hidden lines removed
   CALL AGIHID(.TRUE.)	!remove hidden lines from surface
 			!default is .FALSE.
  
 specify side of surface to be drawn
   CALL AGISID(ISIDE)	!1 to draw upper side, 0 to draw both
 			! -1 to draw lower side
 			!default is 0
Home Top


Miscellaneous

 The following are isometric subroutines you might want to call to do
 additional fine-tuning of a plot.
  
 address screen in 3-D coordinates
   CALL AGICAU(X,Y,Z,IX,IY) !convert user x,y,z to screen ix,iy
  
 read major/minor tick values of z axis (called after AGISOC/AGISOM)
   CALL AGIGZC(NC,C,TIC)
  
   where:
   NC      (integer) number of ticks (.LE.41)
   C       (1-D real array) Z values at the ticks
   TIC     (logical array) corresponds to C array
       if TIC(i) is true, C(I) is a major tick value
       if TIC(i) is false, C(I) is a minor tick value
Home Top


Contour(3D)_plots

 The contour routines draw unlabeled contour lines.  In SGLIB the basic
 contour routines are RCONTR and CONTUR, which are based on routines in
 the MFE TV80 library.  In SGNEW the basic contour routine is AGCLINS,
 which is based on the NCAR CLGEN routine.  The RCONTR and CONTUR
 entries are retained in SGNEW, and make the appropriate calls to
 AGCLINS.

 RCONTR draws level curves (contours) for a function FCN of rectangular
 coordinates specified by one dimensional arrays; i.e.,
 A(i,j)=FCN(X(i),Y(j)).  CONTUR accepts arbitrary two-dimensional
 curvilinear coordinate arrays that divide the x,y-plane into a grid of
 quadrilaterals; x,y-plane into a grid of quadrilaterals; i.e.,
 A(i,j)=FCN(X2(i,j),Y2(i,j)).  AGCLINS allows you to:  specify a
 separate color for each level (4105 mode); put a symbol (a drawn symbol
 or an ASCII character) at intervals along each line; color fill between
 the lines (4105 mode).  If you want ticks and tick labels, you should
 call AGRAPH, AGRCFR, or AGFRAM before calling the contour routine.
Home Top


AGRAPH/AGFRAM

 	CALL BINITT
 	CALL SLIMX(200,800)	!optional
 	CALL SLIMY(200,800)	!optional
 	CALL AGRCFR(X,IMIN,IMAX,ISTEP,Y,JMIN,JMAX,JSTEP,IGRID)
 	CALL RCONTR/CONTUR/AGCLINS
  
 where:
 	X,Y is the X/Y data array
 	IMIN,JMIN is the first index to use in X/Y
 	IMAX,JMAX is the maximum index to use in X/Y
 	ISTEP,JSTEP is the index step size for X/Y
 	IGRID =1 for tick labels on the left and bottom only
 	      =2 for tick labels on the top and right also
Home Top


RCONTR

 	REAL X(51),Y(51)	!independent axes
 	REAL Z(51,51)		!data values
 	REAL C(10)		!contour levels
 	  .  .  .
 	CALL INITT(240)
 	CALL BINITT
 	CALL SLIMX(150,850)
 	CALL SLIMY(100,600)
 	IGRID=1		!ticks on left/bottom only; 2=top/right also
 	CALL AGRCFR(X,1,51,1, Y,1,51,1,IGRID)
 	NC=-10		!10 levels equally spaced between min and max
 	C(1)=ZMIN
 	C(2)=ZMAX
 	CALL RCONTR(NC,C,0, Z,51, X,1,51,1, Y,1,51,1)
 	CALL AGTCHS('X')
 	CALL AGTCVS('Y')
 	CALL UPAUSE(0)
 	CALL FINITT(IX,IY)

 The arguments to RCONTR are:

 CALL RCONTR(K1,C,K2,A,MAX,X,IMIN,IMAX,ISTEP,Y,JMIN,JMAX,JSTEP)
  
 where:	K1,K2	(integers) describe how the contours are specified
 	C	(1-D real array) contour values
 	A	(2-D real array) function values
 	MAX	(integer) the inner dimension of A
 	X,Y 	(1-D real arrays) define a rectangular grid in the
 		x,y plane
 	IMIN	(integer) the minimum i value
 	IMAX	(integer) the maximum i value
 	ISTEP	(integer) the increment between i values
 	JMIN	(integer) the minimum j value.
 	JMAX	(integer) the maximum j value
 	JSTEP	(integer) the increment between j values

 Inputs: K1,C,K2,A,MAX,X2,IMIN,IMAX,ISTEP,Y2,JMIN,JMAX,JSTEP
 Outputs: C (If K1 is less than 0)

 The arguments K1, C, and K2 determine the level lines (contour values)
 to be plotted.  Three plotting options are available in each of the
 contour routines.  The plotting option is selected by K1.

 K1 greater than 0:
   The array C contains K1 numbers to be used as test values for
   plotting the level lines, FCN(X,Y)=C(i).  Those contours C(i) with i
   less than K2 are plotted as a series of dots, while those with i
   greater than or equal to K2 are plotted as solid lines.
 K1 less than 0:
   Minus K1 equally-spaced test values between C(1) and C(2), inclusive,
   are generated and placed in C as output.  The numbers are stored in
   order, with C(1) remaining unchanged and new C(-K1) = OLD C(2).
   Plotting then proceeds as described above.
 K1 equal to 0:
   Then F0 = C(1), DF = C(2), and all level curves of the form FCN = F0
   + M * DF (M is an integer) are plotted (provided they pass through
   the grid).  Those contours less than C(1) are plotted as a series of
   dots, while those greater than or equal to C(1) are plotted as solid
   lines.  In this case, K2 is ignored.  Note that an error exit is
   taken if C(2) is less than or equal to 0 for this option.
Home Top


CONTUR

 CALL CONTUR(K1,C,K2,A,MAX,X2,IMIN,IMAX,ISTEP,Y2,JMIN,JMAX,JSTEP)
  
 where:	K1,K2	(integers) describe how the contours are specified
 	C	(1-D real array) contour values
 	A	(2-D real array) function values
 	MAX	(integer) the inner dimension of A
 	X2,Y2	(2-D arrays) define the coordinization of the x,y plane
 	IMIN	(integer) the minimum i value
 	IMAX	(integer) the maximum i value
 	ISTEP	(integer) the increment between i values
 	JMIN	(integer) the minimum j value
 	JMAX	(integer) the maximum j value.
 	JSTEP	(integer) the increment between j values.
 	
 Inputs: K1,C,K2,A,MAX,X2,IMIN,IMAX,ISTEP,Y2,JMIN,JMAX,JSTEP
 Outputs: C (If K1 is less than 0)

 The arrays X2 and Y2 must be set up so that the four points
  
 	(X2(I,J),Y2(I,J))
 	(X2(I,J+JSTEP),Y2(I,J+JSTEP))
 	(X2(I+ISTEP,J+JSTEP),Y2(I+ISTEP,J+STEP))
 	(X2(I+ISTEP,J),Y2(I+ISTEP,J))

 define a quadrilateral, for any legal choice of (I,J) within the limits
 of IMIN,IMAX and JMIN,JMAX.

 All three arrays (A, X2, Y2) must have the same structure.  That is,
 the same number of rows must be specified for each in the dimension,
 and the number of rows must be equal to the value of MAX in the
 argument list.
Home Top


AGCLINS

  
 	INTEGER KOLORS(6) /2,3,4,5,6,7/
 	INTEGER ISYMBS(6) /2,3,4,5,6,7/
 	PARAMETER (MAXD=20)	!X dimension of data
 	PARAMETER (MAXY=30)
 	REAL XDATA(MAXD), YDATA(MAXY)	!independent axes
 	REAL ZDATA(MAXD,MAXY)		!data
 	REAL CL(40)		!contour levels (max=40)
 	  ...
 	CALL INITT(240)		!init plot
 	CALL BINITT
 	CALL SLIMX(100,700)	!set screen window
 	CALL SLIMY(100,700)
 	CALL AGCLINI(0,0,0)	!init contour package
 	CALL AGCOLRS(6,KOLORS,0)	!set color codes, no fill
 	CALL AGCSYMB(6,ISYMBS,0)	!set contour symbols
 	IGRID=2		!1=ticks on left/bottom, 2=top/right also
 	CALL AGCFRAM(XDATA,NX,YDATA,NY,IGRID)	!axes and ticks
 	!NX = number of X points (and ZDATA points in X direction)
 	!NY = number of Y points (and ZDATA points in Y direction)
 	!ZMIN = minimum ZDATA value
 	!ZMAX = maximum ZDATA value
 	NLEVL = 8	!number of contour levels
 	ZINC = (ZMAX-ZMIN)/NLEVL	!step between levels
 			!set CL to contour levels, NCL to # of levels
 	CALL AGCLGEN(ZDATA,MAXD,NX,NY,ZMIN,ZMAX,ZINC,CL,NCL,ICONST)
 	IF (ICONST.NE.0) <data is constant>
 	CALL AGCLINS(ZDATA,MAXD,XDATA,NX,YDATA,NY,CL,NCL)
 	CALL AGTCGT(0,'TITLE')	!put title
 	CALL AGTCVS('Y AXIS',0)	!y axis label
 	CALL AGTCHS('X AXIS',0)	!x axis label
 	CALL UPAUSE(0)
 	CALL FINITT(0,0)	!done
  
 AGCLINI initializes the contour package and set sizes for temporary
 buffers.  A size of 0 uses the default buffer size.  The first two
 buffers are related to the line drawing routines; the default for these
 is a function of the number of data points.  The third buffer is only
 used when there is color fill between the lines; it defaults to 80000.

 AGCOLRS (optional) sets the sequence of colors for the contour levels.
 If there are more levels than colors the sequence is repeated as
 needed.  The last argument is a flag which controls whether the areas
 between lines are filled.

 AGCSYMB (optional) sets the sequence of symbols for the contour levels.
 If there are more levels than symbols the sequence is repeated as
 needed.  The last argument specifies the distance (number of points)
 between symbols.

 AGCDASH (not implemented yet) sets the sequence of dash styles for the
 contour levels.  Each level is a separate style.

 AGCLGEN (optional) calculates contour levels from the data.  There can
 be at most 40 levels; for most applications 10 levels is probably too
 many.  The values are rounded to "nice" intervals.

 AGCFRAM draws the axes, ticks, and tick labels, the same as AGCRCFR.

 AGCLINS draws the contour levels.  If any of the temporary buffers is
 not big enough, it outputs a message on the plot and exits.

 AGEGET returns an integer status code and optional error text message
 if an error occurred; a status of 0 means no error.
Home Top


_mode

 SGLIB can output either 4014 or 41xx style Tektronix commands.  41xx
 class terminals support a number of features not available for 4014
 terminals: lines (vectors) can have color as well as dash type (the 8
 standard colors are black, white, red, green, blue, cyan, magenta, and
 yellow); in marker mode, the program outputs a set of points and the
 device draws a marker (hardware defined symbol) at each point; text can
 have color, size (multiples of 5x7), and rotation (0, 90, 180, and 270
 degrees); panels are closed regions that can be filled with a color or
 one of about 50 dither patterns.

 Many SGLIB users now have Macintoshes with VersatermPRO, which supports
 the 4105/4107.  There is also a Tektronix Color Copier in the HLDAS
 Data Analysis Room, which is accessed by PRINT/DEV=HC0, and several HP
 terminals which are 4105 compatible.  On the other hand, most other
 terminals (V550, VT240, etc) and the laser printers can not handle 4105
 format.

 While many of the 41xx commands differ from the 4014 commands, this is
 transparent to a program that calls SGLIB routines.  The program can
 contain any 4105 specific subroutines.  At execution time, if 4105 mode
 is selected (the program calls TMINIT(1) before INITT, or the user has
 done DEFINE TERMINAL_4105 YES before program execution), the 41xx
 commands are output; if 4105 is off (the program calls TMINIT(0) or
 logical TERMINAL_4105 is deassigned), the 4014 commands are output.
Home Top


_resolution

 Normally SGLIB draws its output on a screen which is 1024 pixels wide
 and 780 pixels high.  However some graphics devices are capable of
 displaying output to a resolution of 4096 by 4096 pixels.  The
 advantage of 4096 is more accurate data curves, especially with dashed
 and dotted lines -- closer to "publication quality".  The disadvantage
 is that the quantity of output for a dense plot is four to five times
 greater.  All labels and other text are identical between 1024 and
 4096.

 The devices at PPPL which are capable of displaying the higher
 resolution are Tektronics 4014/4025, MacIntosh with VersatermPro, and
 the QMS laser printers.  Other devices (V550, laser printers, etc) can
 process 4096 output but don't give any better resolution than for 1024.
Home Top


Details

 Several routines have been modified to make 4096 screens "transparent
 to the user".  SLIMX/Y, X/YLOC, X/YLEN, and all the AGT routines accept
 arguments assuming that the screen is always 1024 by 780, and
 automatically convert to the proper screen offset.  Tick and axis
 labeling may have moved slightly as the offsets are now calculated,
 where previously they were constants.

 However the basic routines that move and draw in screen units
 (MOVABS/REL, DRWABS/REL, DSHABS/REL, PNTABS/REL) do not convert.  The
 routines that return character sizes do adjust for 4096, but the
 routines that return current "pen" location and screen window do not:
         CALL CSIZE(IWIDT, IHITE)        size of one char, 1024/4096
         IHITE = LINHGT(NLINES)          height of text area, 1024/4096
         IWIDT = LINWDT(NCHARS)          width of text string, 1024/4096
         CALL SEELOC(IX, IY)             pen location, always 1024
         CALL SEETW(MINX,MAXX, MINY,MAXY)  screen window, always 1024
 Thus the output from CSIZE/LINWDT/LINHGT feeds properly into
 MOVABS/REL, etc., and the output from SEELOC/SEETW feeds into AGTxxx,
 but not vice versa.

 There are two ways you can convert screen coordinates that are
 constants or that are return values from the above routines.  One is to
 get the conversion factor (1 for 1024, 4 for 4096) by calling AGSEET
 and doing the arithmetic yourself:
         CALL AGSEET(I4105,KFAC,IC,IS)   KFAC is 4096 factor
         CALL SEETW(MINX,MAXX, MINY,MAXY)
         IW = LINWDT(2)                  width of 2 characters
         CALL AGTMHS(MINX+(IW/KFAC),MAXY+4,"TITLE")
             puts TITLE 2 spaces from left edge, 4 pixels above top
         CALL MOVABS(MAXX*KFAC+IW,(MAXY-20)*KFAC)
             moves to 2 spaces from right edge, 20 pixels below top

 The other is to use the IAGHRES/IAGLRES functions that convert screen
 units to high(4096) or low(1024) resolution:
         CALL SEETW(MINX,MAXX, MINY,MAXY)
         IW = LINWDT(2)                  width of 2 characters
         CALL AGTMHS(MINX+IAGLRES(IW),MAXY+4,"TITLE")
         CALL MOVABS(IAGHRES(MAXX)+IW, IAGHRES(MAXY-20))

 Contour and isometric routines work at 4096, although the isometric Y
 axis labels are slightly off.
Home Top


Usage

 There are two ways to turn on 4096 screen resolution; one is to add
         CALL TERM(0, 4096)
 after calling INITT, but before calling BINITT.  (The first argument
 affects whether dash patterns 1-7 and "point lines" are drawn by the
 device hardware:  a value of 3 means use hardware, 2 means do software
 emulation, 0 leaves the current value unchanged.) To revert to 1024
 resolution,   CALL TERM (0, 1024)   or call INITT.
 The other way is:

         DEFINE TERMINAL_RES 4096
 BINITT now checks logical name TERMINAL_RES each time it is called:  if
 it is not defined, the screen resolution is 1024 (default) or 4096 if
 TERM has been called; if it is defined as 4096, screen resolution is
 set to 4096; if it is defined by anything except 4096, screen
 resolution is set to 1024.  Thus you can override the effect of
 including TERM(0,4096) in a program to speed up output while browsing
 through a file; or you can force 4096 resolution on a program which was
 not intended to be run that way.
Home Top


XPLOT

 XPLOT is a PPL program which permits you to view a plot file on your
 terminal.  It reads from the disk file named on the command line or, if
 none, from the file identified by logical name PLOT.  For output it
 supports the same terminal types (using logical variable TERMINAL_TYPE)
 as SGLIB.  If you don't invoke TFTRLOG, you should have the following
 in your LOGIN.COM file:

         $ SETUP XPLOT

 For more information, see the separate XPLOT help.
Home Top


PSPLOT

 PSPLOT is a PPL command to print a Tektronix plot file on a laser
 printer by first converting it to a PostScript file.  The PostScript
 file is printed and deleted.  This procedure uses the TEK2PS program,
 which is a modification to the shareware TEK2PS that includes support
 for 4105 features.
Home Top


VPLOT

 VPLOT is a PPL program that lets you select frames from a plot file and
 send these to a VGDS destination list (printers and/or control room
 display screens).  For more information see HELP VGDS VPLOT.
Home Top


SGCAT

 SGCAT is a PPL utility that concatenates several plot files into a
 single file.  Because of the file characteristics of plot files,
 concatenating these files using the VMS COPY or APPEND command creates
 files with garbage blocks at the end.  The command format is:
 	SGCAT  inputfiles  outputfile
 where "inputfile[s]" is one or more file names separated by commas, any
 of which can contain wild cards.  An input file can also be modified by
 "/since=<date>", where "date" is dd-mmm-yyyy, dd-mmm, TOD[AY], or
 YES[TERDAY].  Examples:
 	SGCAT abc1.plt,abc2.plt  abc12.plt
 	SGCAT abc*.plt  abc all.plt
 	SGCAT abc.plt.*  allabc.plt
 	SGCAT abc*.plt/since=today  abc today.plt
 	SGGCAT abc*.plt/sin=1-nov  abc month.plt
 While it is concatenating the files, SGCAT inserts a form feed (start
 new page) before the next file if any file does not contain a form
 feed.
Home Top


Glossary

 This section defines some of the terms used in this help file:
 alpha (VT100) screen:  Most terminals and terminal emulators have two
           separate screens or windows, one that conforms to the ANSI
           VT100 standard for text input/output, and one is Tektronix
           compatible.
 40xx mode:  The graphics window can support the Tektronix 40xx class of
           terminals, which includes 4010, 4012, and 4014; SGLIB treats
           all these the same.
 41xx mode:  If the graphics window support the Tektronix 41xx class of
           terminal (4105, 4107, 4115), it has a number of features not
           available in 40xx terminals, including color, rotated text,
           and filled areas.
 page:  In this document the term page means everything between two
           erase commands; i.e., a screen full on a terminal, or a page
           on a printer.
 frame:  A frame is a portion of a page (possibly all), which includes
           some number of data curves, axes, labels, etc.
 axis:  The axis lines are the lines along the bottom and left of a
           frame through which the tick marks are drawn; top and right
           axes can also be drawn.
 ticks:  Tick marks are normally drawn through the X and Y axes and
           labeled at intervals with the data values.
 grid:  When the tick marks are drawn all the way across the frame, they
           create a grid for the frame.
Home Top


History

 This section is a record of when various features were added to SGLIB.
Home Top


_changes

 *-There is a new routine to obtain the character typed by the user at
 the UPAUSE pause:
 	CHARACTER CTYPED*1
 	...
 	CALL UPAUSE(0)		!beep and wait
 	CALL UPAUCH(ITYPED)	!get typed character
 	CTYPED=CHAR(ITYPED)	!convert to a character variable

 *-The internal routine SG NARG has been replaced by the Fortran
 run-time library routine IARGCOUNT.

Home Top


_changes

 *-The text routines (AGTHS, AGTVS, AGTMHS, etc.) no longer accept
 either a character variable/constant or a text string stored in a
 non-character variable.  The argument now MUST be a character variable
 or constant.

 *-The argument to the AGFCLOS routine must be a character variable or
 constant; an integer argument is no longer acceptable.
 	CALL AGFCLOS(' ')	!close any output file
 	CALL AGFCLOS(FILE)	!close and return the file name

Home Top


_changes

 *-UPAUSE, the routine that beeps at the end of a plot and waits for you
 to type a character, now moves the cursor to the bottom left corner of
 the screen if a disk file open where you are optionally storing frames
 based on which character you type (usually "D").

 *-The PPPL utility XTC, an X-window graphics tool that buffers plot
 frames and provides other graphics support, is now supported both for
 plot output and input.  For more information on XTC, see "HELP XTC".

 *-Logical name PLOT (or the destination argument to RINTT) can now
 specify up to 3 simultaneous output devices:  one disk file, the
 terminal attached to your job, and an XTC window or another terminal.

 *-Subroutine RINITT, which changes the plot output device(s), now has
 an optional status argument that returns a status code.  If the status
 argument is not present and the new device(s) are unavailable, RINITT
 causes the program to stop; if present, RINITT returns instead of
 exiting.

 *-If PLOT is undefined in a batch job, and the definition of SYS$OUTPUT
 is a disk name with no directory, the plot is written to the file
         SYS$LOGIN:<user>.PLT
 where <user> is your user name.

 *-New routines AGEXSR and AGEYSR draw error bars with unequal lengths
 for the top/bottom (right/left) sides of the error bar.

 *-Some internal routines have been converted to empty shells that just
 output an error message (KEYSET, DATGET, NOTATE, RECOVX, VWINDO, ULINE,
 UPOINT).  You should only be using routines described in the
 SUBROUTINES section of this help file.
Home Top


_changes

 SGLIB changes made in March, 1991:

 *-There are 4 new symbols:
 	code 12 is a MacCircle (see below)
 	code 13 is a circle with a plus inside
 	code 14 is a square with an X inside
 	code 15 is a diamond with a plus inside
 ONLY for VersatermPro in 4105 mode, the MacCircle draws a true circle
 rather than the hexagon approximation, which is useful when saving a
 VersatermPro graph as a MacDraw document.  In 4014 mode symbol code 12
 is the same as code 1.

 *-SGLIB now supports "solid" symbols.  In 4105 mode, it uses a hardware
 capability (panel fill) to create a solid symbol of the same color as
 the outline.  In 4105 mode all symbols except the vertical bar, up and
 down arrows, and the 3 overlaid symbols have a filled version; a filled
 "X" becomes a bowtie, a filled "+" is a bowtie at a 45 degree angle.
 In 4014 mode a symbol is drawn repeatedly with smaller scale factors to
 emulate solid fill.  (Note that this makes .PLT files bigger and
 increases the time to display the plot.) In 4014 mode the only symbols
 that fill are the circle, square, diamond, triangle, and del.

 *-A new routine AGNPTS(NX,NY) lets you specify the number of points in
 your X and Y arrays separately.  For example, if you have NY points in
 an array YARY, but just a start and delta for the X data, you can do:
 	REAL XARY(4),YARY(NY)
 	...
 	CALL AGNPTS(0,NY)	!X data is short form (NX=0)
 	XARY(1)=-1.		!set up short form descriptor
 	XARY(2)=NY
 	XARY(3)=XSTART
 	XARY(4)=XDELTA
 	CALL CHECK(XARY,YARY)
 	CALL DSPLAY(XARY,YARY)

 *-A new routine, AGSTEPS(ISTEP,ISTART), lets you set both the symbol
 step size (number of points between symbols) and symbol start (first
 point to put a symbol).  This permits staggering symbols on overlaid
 lines.
Home Top


_changes

 SGLIB changes made in February, 1990:

 *-While you are switched to the graphics screen of your terminal, SGLIB
 traps broadcast messages (notification of mail, system bulletins,
 ctrl-T, etc.) and outputs these when you switch back to the alpha
 (VT100) screen.  The size of the buffer is 20 messages, each up to 120
 characters; any more than this are thrown away.
 If your program enables broadcast trapping before calling INITT or
 AGSGRF (e.g., via the SMG routines), the messages go to your buffer and
 SGLIB trapping is not enabled.  Note that while trapping is in effect
 (whether by SGLIB or SMG or any means), you cannot spawn.  SGLIB
 enables trapping any time your program outputs to a terminal; it does
 not check that the terminal is the SYS$OUTPUT device for your job.  You
 can inhibit broadcast trapping by doing "DEFINE TERMINAL_TRAP NO"
 before program execution.

 *-SGLIB now has an exit handler which cleans up any open output.  If
 you type ctrl-Y (or EXIT to DEBUG) while on the graphics screen, just
 type the VMS command EXIT, which terminates the program, to be switched
 back to the alpha screen.  (If you switch manually and then type a VMS
 command a few strange characters - the control sequence to switch
 screens - will appear on your terminal.)  Zero length plot files (from
 having a plot file open where you didn't "keep" any pages) should now
 always be deleted when you exit the program.

 *-You can now set the size of the terminal and/or disk buffers at run
 time via logical variables:
 	DEF SG_TERM_BYTES n	!1 <= n <= 512
 	DEF SG_DISK_BLOKS m	!1 <= m
 The default for SG_TERM_BYTES is 512; for SG_DISK_BLOKS is 3 (disk
 blocks).  The buffers are now allocated dynamically the first time
 output is done to that class of device; they remain allocated (at that
 size) for the duration of the program.  Setting the size of the disk
 buffer to a value greater than the default decreases the number of disk
 i/o's.  A disk block size that is a multiple of the allocation default
 for the disk (3 for most PPL disks) is more efficient, but not
 required.  The main use for changing the size of the terminal buffer is
 debugging; a value of 1 byte guarantees that you can see everything
 that has been generated if the program aborts in the middle of
 execution.

 *-Subroutine RESET is no longer called by any routine in SGLIB, and so
 is needed only if any program calls it directly.  Deleting this routine
 from SGLIB would eliminate possible conflicts with other libraries with
 a routine of the same name.

 *-There is a new routine that returns a flag indicating what types of
 output devices have been selected by the user:
 	CALL AGSEEF(IOUT, IX, IY, IZ)
 IOUT = 0 for no output, 1 for disk only, 2 for terminal only, 3 for
 both.  The other arguments are unused at present.  This routine is
 valid after the user has called INITT the first time.  The IOUT
 parameter is modified by AGVGDS and RINITT.

 *-In 4105 mode, 2 character sizes are supported via subroutine CHRSIZ.
 In 4014 mode, size 1 is the default, 2 is 94% of size 1, 3 is 62%, 4 is
 55%.  In 4105 mode, size 1 is the default, 2 is the same as size 1, 3
 is 60%, and 4 is the same as 3.
Home Top


_changes

 SGLIB changes made in 1989 include:

 *-There is a new routine AGQFILE which queues your plot file to a
 printer.  This is what SGLIB calls if you specify a print queue as a
 VGDS destination.  It is much faster than calling LIB$SPAWN with a
 PRINT command, and can be used to queue any file (not just a plot
 file).  See the Output_select(RINITT,PLOT,AGQFILE) section of this
 help.

 *-The AGISLY routine to set the length of the Y axis for AGISOM/AGISOC
 now automatically calculates a reasonable axis length if you call it
 with the length argument set to zero; e.g., CALL AGISLY(THETA,0).
Home Top


_changes

 SGLIB changes made in 1988 include:

 *-4105 class output is supported.  To enable 4105 mode, DEFINE
 TERMINAL_4105 YES before executing your program; DEAS TERMINAL_4105 to
 return to good old 4014 style output.  AGCGRID(INDEX), AGCCURV(INDEX),
 AGCTEXT(INDEX) set the color for grid (including tick labels),
 curve(s), and text, respectively.  INDEX = 0 for white (no line), 1 for
 black, 2 for red, 3 for green, 4 for blue, 5 for cyan, 6 for magenta, 7
 for yellow.  Call AGCCURV/AGCGRID after BINITT, AGCTEXT anytime after
 INITT.  LINCLR(INDEX) sets color for MOVABS/DRWABS/PNTABS/...

 *-There is a new line type called a marker line, which is an extension
 of a point plot.  Marker type 0 is a dot, 1 a small plus, 2 a larger
 plus, 3 an asterisk, 4 a circle, 5 an X, 6 a square, 7 a diamond, 8 a
 square with a dot, 9 a diamond with a dot, 10 a square with an x.  If
 the line type is -5 (CALL LINE(-5)), a marker line is drawn with the
 marker type set to the symbol type (CALL SYMBL(n)).

 *-AGTMVS/AGTVS (move/write vertical string) write text at 90 rotation
 (heading up the left axis) in 4105 mode.  New routines
 AGTRS(IROT,STRING, [,LENGTH]) and AGTMRS(IX,IY,IROT,STRING,[,LENGTH])
 move/write rotated; the angle IROT must be 0 (horizontal), 90 (heading
 up), 180 (upside down), or 270 (heading down).

 *-Most of the AGX entry points (AGXCHS, AGXCVS, AGXCGT, AGXHS, AGXVS),
 the old-style names for the AGT routines, have been deleted; if you
 have any of these, change the AGX to AGT.
Home Top


Deletions

 Several routines that are described in the Tektronix manual are null in
 SGLIB.
 *-XDEN, YDEN, XETYP, YETYP, and SIZEL set flags which are not
 supported.
 *-HSTRIN, HLABEL, VSTRIN, VLABEL, EFORM, FFORM, IFORM, FONLY, ESPLIT
 were text formatting routines.
 *-USESET would permit user written tick labels.

 Calendar dates as labels, text margins and tab settings, and polar
 plots have been removed.

Home Top


About this document

This Document was created by hlptohtml

  • Written By:
  • Manish Vachharajani(mvachhar@pppl.gov)