RLIB Utility library for ILL-SANS data treatment

R. Ghosh, June 2018


There are current versions of this library available for Linux, Macintosh and Windows The library holds the small amount of system dependent code for the ILL SANS programs. For simplicity no source code is actually shared between platforms. Each directory is self contained and after copying an updated source file the make lib command will compile and build the library. For clean results delete the old library first.
Library Source: rlib.zip

Directory structure

rlib
 |--toolsM	build library for Windows Mingw g77
 |--toolsMgf	build library for Windows Mingw gfortran
 |--toolsL	build library for linux gfortran
 |--toolsO	build library for Macintosh OS X gfortran
 
Similar other versions exist for SGI-IRIX, alpha-osf, HP-UX etc.

Principal Routines

Data access routines

  • RGIO for reading and writing regrouped data
  • RSIO for reading and writing unregrouped data
  • SASAS for reading raw data
  • General (x,y) plotting routine

  • RSPLT a plotting routine for use with PGPLOT
  • SRSPLT a plotting routine for use with PGPLOT
  • Other Utilities

    A number of small routines for handling free format input etc., opening printer files with systematic names are in the library and are used by the SANS program suite. Those which may also be of interest to others include:

  • DAYT a time and date routine
  • TRAPCY traps control-C characters
  • Use of library...
    Summary of routines...


    Data access routines

    These replace the VAX-VMS routines RSV, RSA, and SASINV. The calls have been changed deliberately because of the need now to recognise the formal distinction between character and other data types. If the environment variable "SAS_DEBUG" is set to true then messages are written out as the data are read in.

    RGIO, reads and writes regrouped data

    SUBROUTINE RGIO(IER, MM, IRUN, IRUNX, TEXT, PAR, NDATA, Q, S, ES, PNAME)
    
    IER	integer      out  0 no error, -1 error
    MM      character*1   in  set to 'R' read or 'W' write
    IRUN    integer       in  run number
    IRUNX   integer       in  extension number
    TEXT    character*50 i/o  TEXT(1:20) short title, TEXT(21:50) long title
    PAR     real array   i/o  standard ILL-SANS parameters
                             (1-8) THETA0,X0,Y0,DR,SD,WAV,COLL,CONC
                            (9-16) ISUM,MONITOR,SECT,PHI0,WAV%,SOURCEx,SOURCEy,SAMx
                           (17-24) SAMPLE-y,PIXx,PIXy,ANGSAMNOR,TEMP,TRANS,THICK,spare
                           (25-32) reserved
                           (33-40) unused 
                              dimension   (40)
    NDATA   integer      i/o  number of Q values in file
    Q       real array   i/o  Q             )
    S       real array   i/o  S(Q)          ) typically a maximum of 180 values 
    ES      real array   i/o  error in S(Q) ) see "LIMDAT" below
    PNAME   character*4   in  calling program's name
    
    
    For additional control of the functions of this routine the following COMMON blocks contain useful variables, while keeping the basic call as simple as possible. The COMMON blocks are pre-initialised within the standard library.

    COMMON/RGIOX/NTXT,NPARX
    NTXT    integer      in/out Number of extra lines of text set in XTXT
    NPARX   integer      in/out Number of extra parameters in PARX (max=20)
    
    COMMON/RGIOC/XTXT(10)
    XTXT    character*80 in/out extra text data for storage from retieval
    
    COMMON/RGIOP/PARX(20)
    PARX    real        in/out array of extra parameters
    
    COMMON/RGIOY/NUNIT,NTTY
    NUNIT   integer     in      unit number for i/o operations - default is 32
    NTTY    integer     in      output for error messages - default is 6
    
    COMMON/RGIOL/NDIM,LIMDAT,LIMTXT,LIMPX,IONCE
                     default
    NDIM	integer	    1	    dimensionality of data
    LIMDAT	integer	  180       maximum number of data points 
    LIMTXT  integer    10       maximum number of lines of added text
    LIMPX   integer    20       maximum number of extra parameters
    IONCE   integer     0       flag showing initialisations complete
    
    

    RSIO, reads and writes unregrouped data

    SUBROUTINE RSIO(IER, MM, IRUN, IRUNX, NSET, TEXT, PAR, DAT, ERD, PNAME)
    
    IER	integer      out  0 no error, -1 error
    MM      character*1   in  set to 'R' read or 'W' write
    IRUN    integer       in  run number
    IRUNX   integer       in  extension number
    NSET    integer array i/o
                              NSET(1) number of characters in extra text
                              NSET(2) number of parameters in PAR (40)
                              NSET(3) number of parameters in PARX
                              NSET(4) NX number of row data (x)
                              NSET(5) NY number of column data (y)
                              NSET(6) set to 1 if standard errors follow data
    
    TEXT    character*50 i/o  TEXT(1:20) short title, TEXT(21:50) long title
    PAR     real array   i/o  standard ILL-SANS parameters
                             (1-8) THETA0,X0,Y0,DR,SD,WAV,COLL,CONC
                            (9-16) ISUM,MONITOR,SECT,PHI0,WAV%,SOURCEx,SOURCEy,SAMx
                           (17-24) SAMPLE-y,PIXx,PIXy,ANGSAMNOR,TEMP,TRANS,THICK,spare
                           (25-32) reserved
                           (33-40) unused 
                              dimension   (40)
    DAT     real array    i/o intensity/cell for nset(4) x nset(5) cells  
    ERD     real array    i/o error/cell for nset(4) x nset(5) cells  
    PNAME   character*4   in  calling program's name
    
    Because the SASAS routine is used for reading raw data (extension 0) RSIO can access compressed data directly (see SASAS below).

    Again a number of COMMON blocks contain useful additional control parameters.

    COMMON/RGIOC/XTXT(10)
    XTXT    character*80 in/out extra text data for storage from retieval
    
    COMMON/RGIOP/PARX(20)
    PARX    real        in/out array of extra parameters
    
    COMMON/RSUNIT/NUNIT
    NUNIT   integer      in      unit number for i/o operations (default 33)
    
    COMMON/MAXARR/LTITL,LPARR,LPARX,LDATX
    LTITL   integer      in      maximun number of characters from raw
                                 data (default=512)
    LPARR   integer      in      maximum number of raw data parameters (128)
    LPARX   integer      in      maximum number of extra parameters PARX (20)
    LDATX   integer      in      maximum number of data (16384)
    
    
    When IRUNX is zero this subroutine calls SASAS, and reads the raw data. Otherwise the data are written back and read from files with names:
    
    			tnnnnnn.eee
    e.g.                    t002359.001
    
    where nnnnnn is the run number
    and      eee is the extension number
    
    For use with raw data the following environment variables must be defined SAS_INSTRUMENT and SAS_DATA_PATH.
    SAS_INSTRUMENT     name of instrument
    SAS_DATA_PATH      directory in which the raw data is stored
    
    e.g.  % setenv SAS_INSTRUMENT d22
          % setenv SAS_DATA_PATH /data/d22/           (for the current cycle)
    

    If the environment variable SAS_ERROR is set to NONE then no 2D data for errors will be stored. The resultant datasets are then approximately half-size; statistical errors are still reflected to some degree in the dispersion of local data values about the mean.

    SASAS, reads raw data and compressed raw data

    SUBROUTINE SASAS(IER,IRUN,INST,NOMEXP,DDATE,NT,TITL,NP,PARR,ND,IDON)
    
         reading standard ILL-SANS ascii files
    
    IER        integer            out  0 ok, else -1
    IRUN       integer             in   1&<;=IRUN&<;=999999 run number
    INST       character*4        out  inst field in file
    NOMEXP     character*10       out  nomexp in file
    DDATE      character*20       out  data and time of recording
    NT         integer            out  number of titl characters (a1)
    TITL       character*1 array  out  titl array
    NP         integer            out  number of real parameters PARR
    PARR       real array         out  real parameters
    ND         integer            out  number of integers in spectrum
    IDON       integer array      out  spectrum
    
    Data are read on unit 31, set as default in a common block,
    COMMON/SASASC/NUNIT
    Another  common block /LIMINP/ allows reading to be terminated after 
    having read LIMIT data fields.  It can be used to read the titles,
    for example, without the 4k or 16 k data, when limit=2
    COMMON/LIMINP/LIMIT
    
    

    To locate the raw data it is necessary to define environment variables

    SAS_INSTRUMENT     name of instrument
    SAS_DATA_PATH      directory in which the raw data is stored
    
    e.g.  % setenv SAS_INSTRUMENT d22
          % setenv SAS_DATA_PATH /data/d22/           (for the current cycle)
    
    
    If the environment variable "SAS_DECOMPRESS" is set to the name of the decompress command (e.g. zcat ) then the routine will also search for raw data files with the .Z extension.

    The routine limits input from data files to protect the calling program from being overwritten. These limits are set in a common block.

    
    COMMON/MAXARR/NTITL,NPAR,NPARX,ND
    NTITL	integer		max number of characters in title record (512)
    NPAR    integer		max number of parameters (128)
    NPARX   integer         maximum number of additional parameters (20)
    ND      integer         maximum number of data (16384)
    
    

    RSPLT, general (x,y) plotting routine

    This routine serves a similar function to SPLT, a once commonly used routine for tektronix graphics. Using the PGPLOT library and ILL extensions it is possible to use the same routine for both screen and hardcopy output.

    TEMPLOTE A template example of the use of RSPLT has been prepared.

    SUBROUTINE RSPLT(X,Y,ER,NPT,ITYPE,IER,TX,TY,TEX)
    
    X         real array           in  x data values
    Y         real array           in  y data values
    ER        real array           in  error in y data
    NPT       integer              in  number of data
    ITYPE     integer              in  value 0 draw axes and text only
                                         scale limits in x(1),x(2),Y(1),y(2)
                                       value <0 superimpose plot
                                       value >0 draw axes, text, set
                                       scales to include all x and y
                                       plotting symbols:
                                       1  centered point
                                       2  cross
                                       3  asterisk
                                       4  circle
                                       5  diagonal cross
                                       6  square
                                       7  triangle
                                       8  circle and cross
                                       9  point in circle
                                      10  involute square
                                      11  diamond
                                     100  continuous line
                                     200  dotted line
                                     300  dot-dashed line
    IER      integer                in  0 no error bars, 1 plotted
    TX       character*20           in  title for X-axis
    TY       character*20           in  title for Y-axis
    TEX      character*50           in  general title
    

    Other controls are through the COMMON/SPLTC/VARS(32)

            REAL VARS
    VARS(1)  in  default=0 no cursor after plot, 1. bring up cursor
    VARS(2)  in  start of x-axis in NDC units ( 0.15 used if 0.)
    VARS(3)  in  start of y-axis in NDC units ( 0.1  used if 0.)
    VARS(4) out  minimum x value in user units
    VARS(5) out  maximum x   "   "    "    "
    VARS(6) out  minimum y   "   "    "    "
    VARS(7) out  maximum y   "   "    "    "
    VARS(8) out  no. of ndc units per user unit on x axis
    VARS(9) out    "   "     "    "    "   "   "  Y AXIS
    VARS(11) in  end of x-axis in NDC units (0.85 used if 0.)
    VARS(12) in  end of y-axis in NDC units (0.8  used if 0.)
    
    Apart from controlling the marker cursor the variables 2,3,11,12 allow the graph to be resized and repositioned, and additional curves in a different scale range superposed by rescaling using the values in 5 and 6, and/or 7 and 8.

    SRSPLT, general (x,y) plotting routine

    This routine serves a similar function to RSPLT, but includes options for error bars in both X and Y directions, and offers logarithmic scales. Note: to avoid the fairly high risk in converting negative or zero x,y values to logarithms the routine expects that the values in x,y are already appropriately converted. The same proviso is true for the error bars; it is up to the programmer feeding SRSPLT to decide on what to do when the error bar values are calculated!

    SUBROUTINE SRSPLT(X,Y,XM,XP,YM,YP,NPT,LTP,ITYPE,IER,TX,TY,TEX)
    
    X         real array           in  x data values
    Y         real array           in  y data values
    XM        real array           in  X-ERROR values
    XP        real array           in  X+ERROR values
    YM        real array           in  Y-ERROR values
    YP        real array           in  Y+ERROR values
    NPT       integer              in  number of data
    LTP       integer              in  1 X-lin, Y-linear, 3 X-Log, Y-linear
                                       2 X-lin, Y-Log     4 X-Log, Y-Log
    ITYPE     integer              in  value 0 draw axes and text only
                                         scale limits in x(1),x(2),Y(1),y(2)
                                       value <0 superimpose plot
                                       value >0 draw axes, text, set
                                       scales to include all x and y
                                       plotting symbols:
                                       1  centered point
                                       2  cross
                                       3  asterisk
                                       4  circle
                                       5  diagonal cross
                                       6  square
                                       7  triangle
                                       8  circle and cross
                                       9  point in circle
                                      10  involute square
                                      11  diamond
                                     100  continuous line
                                     200  dotted line
                                     300  dot-dashed line
    IER      integer                in  0 no error bars, 1 Y plotted
                                        2 X plotted, 3 X and Y plotted
    TX       character*20           in  title for X-axis
    TY       character*20           in  title for Y-axis
    TEX      character*50           in  general title
    

    Other controls are through the COMMON/SPLTC/VARS(32) as for RSPLT

    Error Bars
    In both RSPLT and SRSPLT it is left to the user to constrain the error bars within the graph axes. This should be performed at a much lower level within the PGPLOT library, and a request has been forwarded to the author, Tim Pearson.

    General Utilities

    
    SUBROUTINE DAYT(DTIME)
    
    DTIME    character*20          out  Date and time "dd-mmm-yyyy hh:mm:ss"
    
    
    
    SUBROUTINE TRAPCY
    
    COMMON/STOPCY/IXV
    
    IXV       integer              normally 0, set to -1 after receiving ^C
    
    This routine is used primarily to ensure that plotting output files are correctly terminated i.e. although the user has interrupted the program the program detects this and ends under its own control.
    
    SUBROUTINE TRIM(STR,LENSTR)
    
    Returns length of none blank string STR in LENSTR
    
    
    SUBROUTINE TOUP(STR)
    
    Converts string STR to upper case
    
    
    SUBROUTINE LPOUT(PNAM,ICHAN)
    
    PNAM      character*4        in   program name
    ICHAN     integer            in   unit for writing listing file
    
    
    This routine opens a file with a name pnamNNN.lis, where pnam is the four character identifier supplied, and NNN is a sequence number 000 to 999.
    SUBROUTINE LPEND
    
    
    This routine closes the listing file opened by LPOUT. If the environment variable "SAS_AUTO_PRINT_CMD" is set to a command this is then prefixed to the file name and sent to the system to print the results after the file is closed.

    Use of rlib library

    The simplest method of including the library in the compile and edit commands is to create a logical link to the library in the same directory as the other source components:

         % ln -s toolsO/librlib.a librlib.a
    
    Then the program is compiled and loaded with the following:
         % gfortran -o prog prog.f librlib.a
    
    Where the PGPLOT library is also used that too may be assigned to a local directory entry:
         % ln -s pg520osxigf.a.a libpgplot.a
    
    
    
    and the program loaded:
         % gfortran -o pplot pplot.f librlib.a libpgplot.a -lX11
    

    make

    The make command performs a check on the last modification date of components used to construct a program. The date of the result or target file is checked against that of each component (dependencies). These component files may be designated as targets for other components. make will scan all dependencies named and recompile where necessary. The file where make searches for this information by default is makefile; a simple example follows.

    The makefile follows for three programs, p1, which uses no library, prog, using the library librlib.a, and pplot, which in addition uses the PGPLOT graphics library.

    all: p1 prog pplot
    p1: p1.o
    	gfortran -o p1 p1.o
    p1.o: p1.f
    	gfortran -c p1.f
    prog: prog.o librlib.a
    	gfortran -o prog prog.o librlib.a
    prog.o: prog.f
    	gfortran -c prog.f
    pplot: pplot.o librlib.a libpgplot.a
    	gfortran -o pplot pplot.o librlib.a libpgplot.a -lX11
    pplot.o: pplot.f
    	gfortran -c pplot.f
    
    To summarise, the make procedure looks at the target, e.g.
     % make p1
    
    checks that program p1 depends on p1 being more recent than p1.o and p1.o being compiled more recently than the creation date of p1.f If the latter is not true then make uses the command(s) which follow (which must start with a tabulation) to update p1 i.e. it performs the compilation, and then links p1.o to produce a current version of the program. When there are several dependencies then the tree is checked and updated from the deepest level. When a large number of sub-components are present the make procedure limits recompilation to those modules which have been modified during the the current cycle of development. By including the dependency on the libraries the dates of these are also tested, and if one has been updated then the program is relinked.

    In the above case

     % make all
    
    would recompile and reload all the programs with the most recent versions since the file or target "all" has not been found; since "all" is never created "make all" will scan all dependencies for p1 prog and pplot every time the command is given.

    Note: the actual command to perform the compilation etc. is preceded by a tabulation character; the line may be continued to a new line after a backslash character \

    Summary of contents of RLIB (librlib.a)

    Dependencies:
    
    P - uses ILL PGPLOT library
    R - uses other routines within RLIB
    S - some system dependency (primarily between unix and PC systems)
    
    Routine         Depends                 Function
    clear.f         P               Clears non-scrolled text-window
    dayt.f          S               returns date+time
    dircom.f        S               returns list of datafiles
    erase.f         P               erases current plot
    getargp.f       S               portable getarg
    getenv.f (PC)   S               for unix getenv call
    inin.f                          integer free format input
    iniwin.f        S               unix-dummy;windows-sets windowing
    inreal.f                        real free format input
    inreala.f                       real array free format input
    lpend.f                         closes listing file
    lpout.f                         opens listing file with sequenced name
    poscur.f        P               marks and stores cursor position
    marcur.f        P               plots stored cursor positions
    pubess.f        P               draws ILL logo
    repar.f                         transposes D16 raw paras for treated paras
    rgio.f          R               reads/writes regrouped SANS data
    rsio.f          R               reads/writes 2D SANS data
    rsplt.f         P,R             standard x-y plots
    sasas.f         R               reads SANS data from D11,D22,D16
    srsplt.f        P,R             x-y plots including log scales
    system (PC)                     for unix system call
    tdlmr.f                         axis limits
    toup.f                          sets string to uppercase
    trapcy.f        S               traps control+c command
    ttin.f                          free format real data input
    userlog.f       S               logs program+version usage
    wdcd.f                          decodes string to reals
    isleep.c                        sleep routine