TRGRAF

This document describes the call interfaces to user callable
TRGRAF subroutines.

TRGRAF subroutines are interactive "front end" routines to SGLIB
graphics displays of scientific data.  Interactivity is handled
in a menu driven / command line input style using the UREAD library.
UREAD "scripts" can be written to automate the display of data or
generation of plots for printer output.  The routines are written
in FORTRAN-77.

Separate HELP is available for both SGLIB and UREAD.  These HELP
documents contain information that is of value to the user as 
well as the programmer.

General information:
  -- all floating point arguments and arrays are single precision.
  -- f77 CHARACTER arguments are used for data labels.  Generally
     the subroutines accept character strings of any length BUT as
     a practical matter the lengths must be kept short, because,
     SGLIB is emulating a Tektronix terminal page, with limited
     space, and long labels will not fit well.  Usually, 10 to 20 
     characters are recommended for function labels and physical
     units, and, no more than 60 characters for "long" labels.
  -- although the collection of routines in TRGRAF will answer to
     a number of basic display needs, it by no means represents a
     comprehensive solution to data visualization and graphics.
  -- history:  these routines were developed for use in "Ufiles" 
     utilities and in the TRANSP output data display program "rplot".
     Most of the code was written by D. McCune in the years 1978
     to 1988.
Home Top


Precision

The main TRGRAF routines are all written in single precision; all
floating point arrays are declared REAL.

However, a parallel interface is maintained for codes which use
REAL*8 to declare floating point arrays.  For each named routine
in TRGRAF, that name prepended with R8_ gives the REAL*8 version.

Thus, to call GRAFX1 from a REAL*8 code, use R8_GRAFX1, replacing
all REAL arguments and arrays with REAL*8 arguments and arrays.

Similarly, to call GRF3F1 from a REAL*8 code, use R8_GRF3F1.
Home Top


Common_features

Routines which plot 1d functions f(x) work as follows:

(1)  The graph is immediately displayed -- the display takes up
     the full one page display.  Default display rules are:  show
     all data on a linear plot.  Defaults can be modified (see
     routines GAXSPC and GSCSPC.

(2)  The user is offered a "post-plot" menu, which offers options
     to change plot scale, axis types (log or linear), and defaults 
     used for the immediate display in (1).  The plot line styles 
     and length and placement of axes can be modified.  Options
     pertaining to drawing of axes tick marks and gridding lines
     can also be manipulated.

Routines which plot 2d functions f(x,y) work as follows:

(1)  a menu is displayed, in which the user chooses to draw
     an isometric plot, a contour plot, a single slice plot
     or a multiple slice plot.

(2)  each display type offers a "post-plot" menu which allows
     change of scale and similar options.

Home Top


Labeling_peculiarity

For historical compatibility reasons, the dollar sign character 
"$" is used as a terminator in graphics labels.  The "$" is no
longer required to indicate the end of a label, but it will be
used as a terminator if present.  Therefore, "$" characters
should not be placed in the middle of graphics labels passed
to subroutines in the trgraf library.

Home Top


GRAFX1

GRAFX1 -- plot a function f(x), where f is represented as an array
of numbers of length N, and x is an array of numbers of length N
in monotonic increasing order.

call interface:

	SUBROUTINE GRAFX1(X,F,N,XUN,FUN,LBL1,LBL2,LBL3)
C
C  DATA:
	REAL X(N),F(N)
C  LABELS:
	CHARACTER*(*) XUN,FUN,LBL1,LBL2,LBL3

XUN and FUN -- short "units" labels, for x and f, respectively.
LBL1, LBL2 and LBL3 -- long labels.  LBL1 and LBL2 are placed
above the plot frame, LBL3 below.

Home Top


GRAFX2

GRAFX2 -- plot two functions f(x) and f2(x) on the same pair of
axes.  A solid line is used for f(x); a dashed line for f2(x).
Note that f and f2 have the same length and same physical units
labels.

call interface:

	SUBROUTINE GRAFX2(X,F,F2,N,XUN,FUN,LBL1,LBL2,LBL3)
C
C  DATA:
	REAL X(N),F(N),F2(N)
C  LABELS:
	CHARACTER*(*) XUN,FUN,LBL1,LBL2,LBL3

XUN and FUN -- short "units" labels, for x and f, respectively.
LBL1, LBL2 and LBL3 -- long labels.  LBL1 and LBL2 are placed
above the plot frame, LBL3 below.

Home Top


GRAFX3

GRAFX3 -- plot three functions f(x), f2(x), and f3(x) on the
same pair of axes.  Different line styles are used for each
function.  Note that all function arrays have the same length
and the same "units" label.

call interface:

	SUBROUTINE GRAFX3(X,F,F2,F3,N,XUN,FUN,LBL1,LBL2,LBL3)
C
C  DATA:
	REAL X(N),F(N),F2(N),F3(N)
C  LABELS:
	CHARACTER*(*) XUN,FUN,LBL1,LBL2,LBL3

XUN and FUN -- short "units" labels, for x and f, respectively.
LBL1, LBL2 and LBL3 -- long labels.  LBL1 and LBL2 are placed
above the plot frame, LBL3 below.

Home Top


GRAFX4

GRAFX4 -- plot four functions f(x), f2(x), f3(x) and f4(x) on 
the same pair of axes.  Different line styles are used for
each function.  Note that all function arrays have the same 
length and the same "units" label.

call interface:

	SUBROUTINE GRAFX4(X,F,F2,F3,F4,N,XUN,FUN,LBL1,LBL2,LBL3)
C
C  DATA:
	REAL X(N),F(N),F2(N),F3(N),F4(N)
C  LABELS:
	CHARACTER*(*) XUN,FUN,LBL1,LBL2,LBL3

XUN and FUN -- short "units" labels, for x and f, respectively.
LBL1, LBL2 and LBL3 -- long labels.  LBL1 and LBL2 are placed
above the plot frame, LBL3 below.

Home Top


GRAFXF

GRAFXF - plot numeric fit and data points.
A fit function Y(X) is plotted as a solid line, while a sequence
of pairs (X2,Y2) are plotted with data point symbols.

call interface:

	SUBROUTINE GRAFXF(X,Y,N,X2,Y2,N2,
     >                    XUN,YUN,LBL1,LBL2,LBL3)
C
C  DATA:
	REAL X(N),Y(N)  ! NUMERIC FIT DATA CURVE (SOLID LINE)
	REAL X2(N2),Y2(N2)  ! "ORIGINAL" DATA (POINT PLOT)
C
C
C  LABELS:
	CHARACTER*(*) XUN,YUN,LBL1,LBL2,LBL3

XUN and YUN -- short "units" labels, for x and y, respectively.
LBL1, LBL2 and LBL3 -- long labels.  LBL1 and LBL2 are placed
above the plot frame, LBL3 below.

Home Top


GRAFXE

GRAFXF - plot numeric fit and data points, optionally with error
bars shown around each data point.

A fit function Y(X) is plotted as a solid line, while a sequence
of pairs (X2,Y2) are plotted with data point symbols.  Error bar
data and flags are provided.  The flags control whether to draw
horizontal error bars, vertical error bars, or both.  The first
M data points can be drawn with error bars, with M=max(IX2E,IY2E)
and M.LE.N2.

call interface:

	SUBROUTINE GRAFXE(X,Y,N,X2,Y2,N2,IX2E,X2E,IY2E,Y2E,
     >                    XUN,YUN,LBL1,LBL2,LBL3)
C
C  DATA:
	REAL X(N),Y(N)  ! NUMERIC FIT DATA CURVE (SOLID LINE)
	REAL X2(N2),Y2(N2)  ! "ORIGINAL" DATA (POINT PLOT)
C
	REAL X2E(N2)  ! HORIZ. ERROR BARS ON ORIG DATA PTS (OPTIONAL)
	REAL Y2E(N2)  ! VERT. ERROR BARS ON ORIG DATA PTS (OPTIONAL)
C
C    IX2E .GT. 0 IF HORIZ. ERROR BARS ARE TO BE PLOTTED
C    IY2E .GT. 0 IF VERT. ERROR BARS ARE TO BE PLOTTED
C
C      IF .GT. 0 THE NUMBER MAX(IX2E,IY2E)
C    INDICATES THE MAXIMUM NUMBER OF PTS WITH
C    ERROR BARS TO BE DRAWN
C
C   *ERROR BAR DATA* X2E(J) = +/- DELTA(X) UNCERTAINTY ABOUT X2(J)
C           *NOT PLOTTED* IF .LE. 0.0
C
C   *ERROR BAR DATA* Y2E(J) = +/- DELTA(Y) UNCERTAINTY ABOUT Y2(J)
C           *NEITHER X NOR Y ERROR BAR PLOTTED* IF .LE. 0.0

XUN and YUN -- short "units" labels, for x and y, respectively.
LBL1, LBL2 and LBL3 -- long labels.  LBL1 and LBL2 are placed
above the plot frame, LBL3 below.

Home Top


GAXSPC

GAXSPC -- set axes types defaults for upcoming f(x) plots.

call interface:  CALL GAXSPC(IARG), where:

  INTEGER IARG

axes select:
  IARG=1 means:  linear-X, linear-Y
  IARG=2 means:  linear-X, logarithmic-Y
  IARG=3 means:  logarithmic-X, logarithmic-Y
  IARG=4 means:  logarithmic-X, linear-Y

Home Top


GSCSPC

GSCSPC -- set plot scaling defaults for upcoming f(x) plots.

call interface:  CALL GSCSPC(IAXIS,ICODE,ZARG1,ZARG2)

  INTEGER IAXIS, ICODE
  REAL    ZARG1, ZARG2    ! not always used... depends on rule...

axis choice:
  IAXIS=1 -- this call sets rules for X AXIS
  IAXIS=2 -- this call sets rules for Y AXIS

rule choice:
  ICODE=1 -- fully automatic, to cover min and max range of data.
  ICODE=2 -- manual:  set scale by prompting user for choice.
  ICODE=3 -- fixed:  all plots set to the same scale.
             (arguments ZARG1 and ZARG2 specify the fixed scale).
  ICODE=4 -- upper limit automatic, lower limit = fixed multiple
             of upper limit.  Used e.g. to control number of 
             decades in a log plot.  ZARG1 specifies the multiplier.
  ICODE=5 -- lower limit automatic, upper limit = fixed multiple
             of lower limit.  ZARG1 specifies the multiplier.

Home Top


GMMSEL

GMMSEL -- select and draw contours

Given a set of contours the user interactively chooses a subset
for plotting.  Each plot can contain up to 15 contours.  The
limit of 15 is due to screen space issues for labeling.

The countours chosen from are a set of sequences of (R,Z) pairs
represented in a particular form.  All sequences contain the
same number of pairs.

Calling interface:

C
C  GENERATE PLOT OF MULTIPLE CONTOURS (R,Y), INDEXED BY Z
C
	SUBROUTINE GMMSEL(R,Y,ND1,NC,Z,NZ,
     >     RUN,YUN,ZLAB,ZUN,MNLAB,KYLAB,FZLAB)
C
C  R(ND1,NZ)
C  Y(ND1,NZ)  SEQUENCES OF ORDERED PAIRS (R,Y) TO BE PLOTTED
C             R MAPPED ALONG HORIZONTAL AXIS, Y ALONG VERTICAL AXIS
C             ND1= 1ST DIMENSION OF R,Y ARRAYS
C
C  NC         NUMBER OF PTS IN EACH CONTOUR (.LE. ND1)
C             (R(1,J),Y(2,J)), (R(2,J),Y(2,J)), ..., (R(NC,J),Y(NC,J))
C
C  Z(NZ)      CONTOUR INDEXING  JTH CONTOUR IS ASSOCIATED WITH Z(J)
C
C  RUN        10 CHAR LABEL PHYSICAL UNITS OF R
C  YUN        10 CHAR LABEL PHYSICAL UNITS OF Y
C
C  ZLAB       10 CHAR LABEL FOR Z
C  ZUN        10 CHAR LABEL UNITS OF Z
C
C  MNLAB      3 60 CHAR "MAIN" LABELS FOR MULTIPLOT
C    MNLAB(1),MNLAB(2) APPEAR ABOVE PLOT  MNLAB(3) APPEARS BELOW
C
C  ** CALLER SUPPLIES ALL OF THE ABOVE **
C
C  KYLAB      5 17 CHAR "KEY" LABELS FOR MULTIPLOT
C
C  ** KYLAB(3) THRU KYLAB(5) MAY BE SET BY CALLER.  THESE LABELS APPEAR
C  AT THE BOTTOM OF THE KEY BOX IN THE PLOT
C
C  FZLAB      15 11-character FIXED PT. (Z) LABELS FOR MULTIPLOT
C
C  KEY LABELS 1 AND 2, AND
C  ALL FIXED Z LABELS SET UP HERE.
C
C  SEE SUBROUTINES GRFMM1 AND MULCDR
C
	REAL R(ND1,NZ),Y(ND1,NZ),Z(NZ)
C
	CHARACTER*(*) RUN,YUN,ZLAB,ZUN,FZLAB(15)
C
	INTEGER ISELF(15)
	REAL ZSELF(15)
C
	CHARACTER*(*) MNLAB(3)
	CHARACTER*(*) KYLAB(5)

Home Top


GRFMM1

GRFMM1 -- plot a set of contours and then offer a post plot menu.
  Each contour is an ordered sequence of (R,Y) pairs, specified to
  the routine in a particular way (see arguments description below).
  The number of points in the sequence can vary from one contour to
  the next, as described.

calling interface:

	SUBROUTINE GRFMM1(R,Y,ND1,NC,NNC,Z,NZ,ISELF,NSEL,
     >     RUN,YUN,MNLAB,KYLAB,LBSEL)

C  ARGUMENTS -- ALL MUST BE SUPPLIED BY CALLER (OUTPUT IS GRAPH)
C
C  IN COMMON/DPLOT1/  XMIN,XMAX,YMIN,YMAX -- THE SCALE OF THE GRAPH
C
C  PASSED:
C   R(ND1,NZ)  DATA BUFFER OF INDICATED DIMENSIONS-- HORIZONTAL CONTOUR
C              PARAMETRIZATION
C   Y(ND1,NZ)  DATA BUFFER OF INDICATED DIMENSIONS-- VERTICAL CONTOUR
C              PARAMETRIZATION
C
C     the i'th point in the j'th contour is at (R(i,j),Y(i,j))
C
C  **NC** IS THE ACTUAL NUMBER OF PTS IN EACH CONTOUR (.LE.ND1)
C   NC(NNC) -- NC(1) IS THE NO. OF PTS IN THE 1ST CONTOUR ...
C              NC(MIN(NZ,NNC)) IS THE NO. OF PTS IN THE NZ'TH CONTOUR
C              NOTE THAT BY PASSING NNC=1 ONE MAY SPECIFY THE SAME
C              NO. OF POINTS IN ALL CONTOURS, OR BY SETTING NNC=NZ
C              AND FILLING THE NC INTEGER ARRAY ONE MAY HAVE A DIFFERENT
C              NO. OF POINTS FOR EACH CONTOUR.  HOWEVER,
C                  2 .LE. NC(J) .LE. ND1
C              MUST BE MAINTAINED FOR ALL J BTW 1 AND MIN(NZ,NNC)
C
C   Z(NZ)      CONTOUR INDEXING
C
C   ISELF(NSEL) SELECTS WHICH CONTOURS ARE TO APPEAR
C     ON THE MULTIPLOT.
C   **NSEL** IS THE NUMBER OF CURVES TO APPEAR ON THE MULTIPLOT
C     the contours that appear correspond to 
C       Z(iself(1)), Z(iself(2)), ..., Z(iself(NSEL)).
C
C   -----------
C   CHARACTER LABELS:
C   ------------
C    RUN        10 CHAR HORIZONTAL AXIS PHYSICAL UNITS LABEL
C    YUN        10 CHAR VERTICAL AXIS PHYSICAL UNITS LABEL
C
C   MNLAB       3 60 CHARACTER "MAIN LABELS"-- 1ST TWO APPEAR
C               ABOVE GRAPH, LAST ONE BELOW
C   KYLAB       5 17 CHARACTER KEY LABELS -- 1ST TWO APPEAR
C               AT TOP OF KEY BOX, LAST THREE AT BOTTOM
C   LBSEL(NSEL) NSEL 10 CHARACTER SELECT LABELS-- 10 CHARACTERS
C               TO ID EACH CURVE IN THE MULTIPLOT (1,2,... NSEL)
C
C *NOTE LABELS DO *NOT* NEED TO BE TERMINATED WITH "$", BUT A "$" IN
C  THE LABEL WILL CHOP OFF OUTPUT OF THE LABEL AT THAT POINT***

-------------

Note the character labels are received as variable length 
(i.e. declared CHARACTER*(*) in the subroutine code body).  The
indicated lengths are the recommended values-- strong constraints
are imposed by Tektronix 4010 screen real estate issues.

By default, GRFMM1 expects its "R" and "Y" dimensions to have
the "same units of length", so that constraints are placed on
plot rescaling to keep square the range plotted over.  To 
disable this, set iself(1) to a negative value; -iself(1) then
indexes the first contour.  My apologies for this kluge.

Home Top


GRF3F1

GRF3F1 -- offer a menu of display options for labeled numeric
  data of the form f(x,y).  The display options include:

    3d isometric plot (user options allow specification of
       linear or log scaling on any of the 3 axes; user 
       options also allows specification of a subdomain
       for plotting).

    contour plot (user options are available to control 
       the selection of contour test values and the domain
       plotted over).

    simple slice plots f(x) at fixed y or f(y) at fixed x.
       The standard f(x) post plot menu is offered.

    slice "multiplots" -- several slices on the same pair 
       of axes.  The standard f(x) post plot menu is offered.

The arguments to GRF3F1 require specification of data and plot
labels.  In addition, an array of length at least ny must
be provided as workspace.  For most applications the
"processing code" IPROC should be left equal to zero.

calling interface:

	SUBROUTINE GRF3F1(X,Z,Y,WK,NX,NY,NZ1,
     >                    XLAB,ZLAB,YLAB,
     >                    XUN,ZUN,YUN,
     >                    ZTITLE,ZLABEL,IPROC)
C
	REAL X(NX)	! 1ST INDEP. COORD OF FCN TO BE PLOTTED
	REAL Z(NZ1,NY)	! FCN TO BE PLOTTED
	REAL Y(NY)	! 2ND INDEP. COORD OF FCN TO BE PLOTTED
	REAL WK(NY)	! ** WORKSPACE ** MUST BE PROVIDED
C
C  X AND Y MUST BE IN ASCENDING ORDER.
C  CAREFULLY NOTE DIMENSIONING OF Z -- NZ1 must be .GE. NX.
C
C  WK WILL BE OVERWRITTEN ON CALL TO THIS ROUTINE
C
C  RECOMMENDED NOT LONGER THAN CA. 30 CHARACTERS...
	CHARACTER*(*) XLAB  ! LABEL FOR 1ST INDEP. COORDINATE
	CHARACTER*(*) ZLAB  ! LABEL FOR FCN BEING PLOTTED
	CHARACTER*(*) YLAB  ! LABEL FOR 2ND INDEP. COORDINATE
C
C  RECOMMENDED NOT LONGER THAN CA. 20 CHARACTERS...
	CHARACTER*(*) XUN   ! UNITS LABEL FOR 1ST INDEP COORDINATE
	CHARACTER*(*) ZUN   ! UNITS LABEL FOR FCN BEING PLOTTED
	CHARACTER*(*) YUN   ! UNITS LABEL FOR 2ND INDEP. COORDINATE
C
C  RECOMMENDED NOT LONGER THAN CA. 45 CHARACTERS...
	CHARACTER*(*) ZTITLE	! TITLE LABEL FOR PLOTS
C
C  RECOMMENDED NOT LONGER THAN CA. 15 CHARACTERS
	CHARACTER*(*) ZLABEL	! GENERIC LABEL FOR PLOTS
C
C  PROCESSING FLAG (FOR LABELING ONLY)
	INTEGER IPROC	    ! 0=NOTHING, 1=AVG'D, 2=SMOOTHED, ETC...

Home Top


GRF3F2

GRF3F2 -- comparitive plots of two functions f1(x,y) and f2(x,y).
  this routine is very similar to GRF3F1, except that the simple
  slice plots show two curves, overlaying data from f1 and f2.
  Note that f1 and f2 must have the same dimensioning.

call interface:



	SUBROUTINE GRF3F2(X,Z,Z2,Y,WK,NX,NY,NZ1,
     >                    XLAB,ZLAB,ZLAB2,YLAB,
     >                    XUN,ZUN,YUN,
     >                    ZTITLE,ZLABEL,IPROC)
C
	REAL X(NX)	! 1ST INDEP. COORD OF FCN TO BE PLOTTED
	REAL Z(NZ1,NY)	! FCN TO BE PLOTTED
	REAL Z2(NZ1,NY)	! 2ND FCN TO BE PLOTTED
	REAL Y(NY)	! 2ND INDEP. COORD OF FCN TO BE PLOTTED
	REAL WK(NY,2)	! ** WORKSPACE ** MUST BE PROVIDED
C
C  X AND Y MUST BE IN ASCENDING ORDER.
C  CAREFULLY NOTE DIMENSIONING OF Z  --  NZ1.ge.NX required!
C
C  WK WILL BE OVERWRITTEN ON CALL TO THIS ROUTINE
C
C  RECOMMENDED NOT LONGER THAN CA. 30 CHARACTERS...
	CHARACTER*(*) XLAB  ! LABEL FOR 1ST INDEP. COORDINATE
	CHARACTER*(*) ZLAB  ! LABEL FOR FCN BEING PLOTTED
	CHARACTER*(*) ZLAB2 ! LABEL FOR 2ND FCN BEING PLOTTED
	CHARACTER*(*) YLAB  ! LABEL FOR 2ND INDEP. COORDINATE
C
C  RECOMMENDED NOT LONGER THAN CA. 20 CHARACTERS...
	CHARACTER*(*) XUN   ! UNITS LABEL FOR 1ST INDEP COORDINATE
	CHARACTER*(*) ZUN   ! UNITS LABEL FOR FCN BEING PLOTTED
	CHARACTER*(*) YUN   ! UNITS LABEL FOR 2ND INDEP. COORDINATE
C
C  RECOMMENDED NOT LONGER THAN CA. 45 CHARACTERS...
	CHARACTER*(*) ZTITLE	! TITLE LABEL FOR PLOTS
C
C  RECOMMENDED NOT LONGER THAN CA. 15 CHARACTERS
	CHARACTER*(*) ZLABEL	! GENERIC LABEL FOR PLOTS
C
C  PROCESSING FLAG (FOR LABELING ONLY)
	INTEGER IPROC	    ! 0=NOTHING, 1=AVG'D, 2=SMOOTHED, ETC...

Home Top


GRF4F1

Visualize f(x,y,z) gridded labeled data.  The routine gives a menu
for specifying which slice to look at (e.g. f(x,y) @ fixed z, or
f(x,z) @ fixed y, etc.).  Then, it calls GRF3F1 on the selected 
slice.

call interface:

      subroutine grf4f1(f,nf1,nf2, x,nx, y,ny, z,nz,
     >   flab, xlab,ylab,zlab, funs, xuns,yuns,zuns,
     >   ztitle, iproc)
c
c  dmc 12 Aug 2000 -- trgraf "slicer" for f(x,y,z) gridded data
c
c  input:
      real f(nf1,nf2,nz)                ! the data
      real x(nx)                        ! x grid (1st dim.), nx.le.nf1
      real y(ny)                        ! y grid (2nd dim.), ny.le.nf2
      real z(nz)                        ! z grid (3rd dim.)
c
      character*(*) flab                ! data label (recommend <~20 chars)
      character*(*) xlab                ! x label (recommend <~10 chars)
      character*(*) ylab                ! y label (recommend <~10 chars)
      character*(*) zlab                ! z label (recommend <~10 chars)
c
      character*(*) funs                ! data units (recommend <~10 chars)
      character*(*) xuns                ! x units (recommend <~10 chars)
      character*(*) yuns                ! y units (recommend <~10 chars)
      character*(*) zuns                ! z units (recommend <~10 chars)
c
c 40 characters or so:
      character*(*) ztitle              ! general title label for all plots
c
c for Ufiles/grf3 compatibility.  if in doubt set iproc=0
c
      integer iproc               !0=NOTHING, 1=AVG'D, 2=SMOOTHED, ETC...
c
c output:
c
c  **sglib tekvec plots, via grf3f1**

Home Top


Loading

On unix systems:
      -L${NTCCHOME}/lib -luflib -lmds_sub -lufhdf -lmdstransp -rplot_sub
                     -ltrgraf -lrp_kernel -lrplot_io -lureadsub
                     -xdatmgr -lsg -lcomput -lvaxonly -lelvislib -portlib
      -L${MDSPLUS_DIR}/lib -lMdsLib -L${NETCDFHOME}/lib -lnetcdf -lhdf_dummy

See $NTCC_ROOT/etc/Make_sample.

Note to Non-PPPL sites:
Verify above directory names with your systems administrator.
If you don't have the netcdf and hdf libraries, link with 
-lcdf_dummy -lhdf_dummy -lmds_dummy.
Home Top


About this document

This Document was created by hlptohtml

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