System Interface Reference Manual

Following is a brief description of all s_i routines. The name of the file containing the source is also reported. Note that some routines are not available on both VAX and Unix.

BATCH routine

This routine determines if the program is being run in a batch job. The routine can be found in the file BATCH.CDF.

      SUBROUTINE BATCH(LBATCH)

      Input  Arguments:  
      -----------------
             None

      Output Arguments:
      -----------------
             LBATCH  (Logical) :     .TRUE. if running in Batch,
                                     .FALSE. otherwise.

BITPAK routine

This routine packs 32 bit data into an array. The function value is a 32-bit integer packing data in array DATA. If a field is overflowing then if MODE.GT.0 the field is filled by 1's ,if MODE.EQ.0 only less significant bits are stored. This routine can be found in the file BITPAK.CDF.

      INTEGER FUNCTION BITPAK(MODE,NDATA,DATA,NBIT)

      Input  Arguments:
      ----------------
            MODE  (Integer*4) : 
                        =0  no data checking; =1 report an error if
                        any (datum.GT.2**nbit); =2 report an error
                        if any (datum.GE.2**nbit); =3 as for 2 but
                        error is fatal.
            NDATA (Integer*4) : 
                        Number of data to be packed
            DATA  (Integer*4) : 
                        Array of NDATA data
            NBIT  (Integer*4) : 
                        Array of bit widths of NDATA data fields

      Output Arguments:
      -----------------
             None

BITUPK routine

This routine unpacks the word WORD and store fields in array DAT. This routine is in the file BITUPK.CDF.

      SUBROUTINE BITUPK(WORD,NFIELD,DAT,NBIT)

      Input  Arguments:
      ----------------
             WORD    (Integer*4) : Word to unpack
             NFIELD  (Integer*4) : Number of data fields
             NBIT    (Integer*4) : Number of bit of each field
 
      Output Arguments:
      -----------------
             DAT     (Integer*4) : Array of NFIELD data
 

CHKLOG routine

This subroutine is designed to check for the presence of the logical symbol LOGNAM, and if it is not found, either demand that the user specify it, or supply a default logical symbol. This routine is in the file CHKLOG.CDF.

      SUBROUTINE CHKLOG(LOGNAM,DEFTRN,LOGTRN,IERROR)

      Input  Arguments:
      ----------------
             LOGNAM  (Character*(*)) The logical name to be translated.
             DEFTRN  (Character*(*)) The default name to be used.

      Output Arguments:
      -----------------
             LOGTRN  (Character*(*)) The translation of "CDFINP".
             IERROR  (Integer*4)     Error status flag.

CRELOG routine

This subroutine creates an entry in the logical name table which associates a specified logical name with an equivalence name. The creation is attempted in the process logical name table with the access mode set to user. This routine is only available on OpenVMS. This routine is in the file CRELOG.CDF.

      SUBROUTINE CRELOG(LGCLNM,EQLNAM,IERROR)

      Input  Arguments:
      ----------------
             LGCLNM  (Character*(*)) :
                             logical name to be defined.
                             Maximum of 132 characters in length.

             EQLNAM  (Character*(*)) : 
                             equivalence name.
                             Maximum of 132 characters in length.
                             Blank characters are not allowed - the first
                             blank character signifies the end of the
                             equivalence name.

      Output Arguments:
      -----------------
             IERROR      (Integer*4) :     
                             Error code as defined in C$INC:ERLEVL.INC.

DEBUG routine

This subroutine determines if the current image is being run under the Debugger This routine is in the file DEBUG.CDF.

      SUBROUTINE DEBUG(LDEBUG)

      Input  Arguments:
      ----------------
             None

      Output Arguments:
      -----------------
             LDEBUG  (Logical):  .TRUE. if running under the Debugger,
                                 .FALSE. otherwise.

DECLEX routine

This routine declares an exit handling routine which will be called upon exiting of the main program. This routine is only available for OpenVMS systems. The exit handling routine will be passed a single argument ndicating an exit status. See the VMS run time library manual for more details. This routine is in the file DECLEX.CDF.

      SUBROUTINE DECLEX(EXIHND)

      Input  Arguments:
      ----------------
             EXIHND  (external) : Name of routine to be called upon
                                  termination of the main program.

      Output Arguments:
      -----------------
             None

DISMOU routine

This VAX/VMS specific routine allows the user to dismount mounted volumes and/or volume sets. A volume/volume set being previously mounted. This routine is in the file DISMOU.CDF.

      SUBROUTINE DISMOU(DEVNAM,IERROR)

      Input  Arguments:
      ----------------
             DEVNAM  (Character*(*)): The device to be dismounted.
                                  

      Output Arguments:
      -----------------
             IERROR  (Integer*4):     Error condition flag.

FTNSTRLEN routine

Integer function that returns the length of a fortran string. Since in fortran there is not such a thing like a null terminated string, we suppose that a fortran string ends at the first blanck character. if there are not such a characters the maximum input lenght is returned. This function is only callable from C. This routine is in the file SILDIR.C.

      int ftnstrlen(const char *str, int maxlen)

      Input  Arguments:
      ----------------
             str (const char *str): The input string (really it 
				    is a character buffer)
             maxlength (int):       The maximum string length.
                                  

      Output Arguments:
      -----------------
             None


      Function Value:
      --------------
             The number of characters before a blank occurs 
	     or maxlength if there are no blanks.

I2PAK routine

This subroutine packs two INTEGER*2 words into an INTEGER*4 word in a "machine independent" fashion. This routine is in the file I2PAK.CDF.


      SUBROUTINE I2PAK(I2,J2,K4)

      Input  Arguments:
      ---------------
             I2 - (INTEGER*2) : first word to be packed
             J2 - (INTEGER*2) : second word to be packed

      Output Arguments:
      ----------------
             K4 - (INTEGER*4) : 
                       packed word whose least significant 16 bits are
                       I2 and most significant 16 bits are J2.


I2UPAK routine

This subroutine unpacks an INTEGER*4 word into two INTEGER*2 words in a "machine independent" fashion. This routine is in the file I2UPAK.CDF.

      SUBROUTINE I2UPAK(I2,J2,K4)

      Input  Arguments:
      ----------------
             K4 - (INTEGER*4) : word to be unpacked.

      Output Arguments:
      -----------------
             I2 - (INTEGER*2) :  
                      result of unpacking least significant 16 bits of K4
             J2 - (INTEGER*2) :
                      result of unpacking most  significant 16 bits of K4

INITIM routine

This routine initializes the timing statistics package for routine 'NAM'. It should be called once for each routine to be timed. This routine is in the file INITIM.CDF.

      SUBROUTINE INITIM(NAM,IERR)

      Input  Arguments:
      ----------------
             NAM  (Character*(4)) : 
                          char string labeling routine to be timed 
                          (20 or less char)

      Output Arguments:
      ----------------
             IERR     (INTEGER*4) : error code:
                                    0 = success
                                    1 = too many routine names 
                                    (this routine will not be timed)

ITIMER routine

This routine returns the CPU time used since process login or since last call to ITIMER. This routine is in the file ITIMER.CDF.

      INTEGER FUNCTION ITIMER(IMODE)

      Input  Arguments:
      ----------------
             IMODE  (Integer*4) : 
                            Flag indicating when timing is with
                            respect to.
                    0       return elapsed CPU time since begin of process.
                    1       return elapsed CPU time since last ITIMER call
                            with IMODE = 0.

      Output Arguments:
      -----------------
             ITIMER (Integer*4) :   
                            Elaspsed CPU time in units of
                            miliseconds.  Resolution is 10 msec.

MOUNT routine

This VAX/VMS specific routine allows the user to mount mounted volumes and/or volume sets. This routine is in the file MOUNT.CDF.

      SUBROUTINE MOUNT(DEVNAM,VOLNAM,IERROR)

      Input  Arguments:
      ----------------
             DEVNAM  (Character*(*)) : 
                            The name of the device to be mounted.

             VOLNAM  (Character*(*)) :
			    The name of the volume to be mounted.

      Output Arguments:
      -----------------
             IERROR  (Integer*4) :
                            Error condition flag.
		     ERSUCC - Success
		     ERWARN - Warning
		     EREROR - Failure
		     ERSEVR - Severe Error

N$A routine

This Subprogram is a Dummy function. Users who pass the externally declared N$A function where optional arguments are allowed will allow subroutines to check the address of optional arguments against the address of N$A. Args that match the N$A address are ignored. This routine is in the file NOARGLIB.CDF.

      INTEGER   FUNCTION N$A()

      Input  Arguments:
      ----------------
             None

      Output Arguments:
      -----------------
             None

SICPRN routine

Compare a pattern against a string to check for a match.

      LOGICAL FUNCTION SICPRN(PATT, STRNG)

      Input  Arguments:
      ----------------
             PATT  (Character*(*)):	Pattern
	     STRNG (Character*(*)):	String

      Output Arguments:
      -----------------
             None

      Function Value:
      --------------
             SICPRN	.TRUE.  - If PATT is found in STRNG
	     		.FALSE. - If PATT is not found in STRNG

SICSCL routine

Terminate/close a link to a remote Socket.

  UNIX

   FORTRAN context : Called via "status = sicscl(sock)";
                     sock is an integer socket index.
 
   VAX
   FORTRAN context : Called via "status = sicscl(sock)";
                     sock is an integer socket index.
 
   sicscl returns:  SKCLOSE_SUC for success, 
                    or SKCLOSE_ERR for failure

   The return codes are defined in s_i$library:siernt.h.

SICSOP routine

This routine opens a connection to a remote socket. The server is cofigured as part of a remote VAX's MULTINET server.

   UNIX

    FORTRAN context : Called via "status = sicsop(server,port)"; server is a
                      character VAX node name passed by reference and port
                      is an integer port number passed by reference.

    VAX
    FORTRAN context : Called via "status = sicsop(server,port)"; server is a
                      character VAX node name passed by address of descriptor
                      and port is an integer port number passed by reference.
 
 
   sicsop returns: Function Value :A valid socket index, or SKOPEN_ERR.

SICSRD routine

This routine read reclen bytes from the connected socket on the specified remote TCP/IP node.

   UNIX

   FORTRAN context : Called via "status = sicsrd(sock,reclen,buffer)"; sock is
                     an integer socket index passed by reference, reclen is an
                     integer record length (passed by ref) in bytes , buffer
                     is an integer buffer array (passed by ref) of length
                     reclen/4 longwords.
 

SIDATI routine

This subroutine returns date and time. It is in the file SIDATI.C.

      INTEGER SIDATI(RESPONSE)

      Input  Arguments:
      ----------------
             None

      Output Arguments:
      -----------------
             RESPONSE (Integer):
			   Returns an array of 6 integers as follows,
                	   with FORTRAN 1-based indexing:
                	   [1]: seconds after the minute - [0, 59]
	                   [2]: minutes after the hour - [0, 59]            
	                   [3]: hour since midnight - [0, 23]
                	   [4]: day of the month - [1, 31]
                	   [5]: month number (January is 1, etc.)
                 	   [6]: year number, e.g. 1994
                	   The conversion to formated time is by the 
			   algorithms within the operating system library.
                	   All entries will be set to -1 if the current time
                	   could not be obtained or converted.

      Function   Value:
      -----------------
		SISUCC		Success
		SIFAIL		Failure

SIDELE routine

This routine deletes a file (due to VAX semantics, the file should be closed. Accepts a character string argument:
[1]: The name for the file

This routine is in the file SIFILEOPS.C.

      Input Arguments:
      ---------------
            FILENAME  (Character):     File name

      output Arguments:
      ----------------
            SIDELE    (Integer):       SISUCC  Success
                                       SIFAIL  Generic Failure

SIFCER routine

This subroutine clears ERROR indication on a C language stream file Accepts an integer:
[1]: integer containing a FILE *.

This routine is in the file SIFILEOPS.C.

N.B. This is a subroutine; there is no return value.

        SUBROUTINE SIFCER(FD)

        Input Arguments:
        ---------------
              FD       (Integer):      FILE *

        output Arguments:
        ----------------
              None

SIFEOF routine

This routine check for EOF on a C language stream file. Accepts an integer:
[1]: integer containing a FILE *. 

This routine is in the file SIFILEOPS.C.

       INTEGER FUNCTION SIFEOF(FD)

       Input  Arguments:
       ---------------
              FD       (Integer):      FILE *
         
       Output Arguments:
       ----------------
              None

       Function  Value:
       ----------------
              SIFEOF   (Integer):      0  Not EOF
                                       1  EOF

SIFERR routine

This routine check for ERROR on a C language stream file.Accepts an integer:
[1]: integer containing a FILE *.

This routine is in the file SIFILEOPS.C.

	INTEGER FUNCTION SIFERR(FD)

        Input  Arguments:
        ----------------
               FD      (Integer):      FILE *

        Output Arguments:
        ----------------
               None

        Function  Value:
        ----------------
               SIFERR  (Integer):      0  No error
                                       1  Error

SIFISC routine

This Subprogram parses a filename VAX format and returns one of its component: node,device, directory,file name, file type, and version number.This routine is in the file SIFISC.CDF.

       INTEGER   FUNCTION SIFISC(FILNAM,FIFUNC,FICOMP)

       Input  Arguments:
       ----------------      
              FILNAM (Character):     File Name VAX Format
              FIFUNC (Character):     Function Code: NODE,DEVICE,DIRECTORY,
                                                     NAME,TYPE,VERSION
       Output Arguments:
       -----------------
              FICOMP (Character):     File Name Component.

       Function Value:
       --------------
              SIFISC                  SISUCC   Success
                                      SIFAIL   Generic failure

SIFLCL routine

This routine close a C language stream file.Accepts an integer:
[1]: integer containing a FILE *.

This routine is in the file SIFILEOPS.C.

	INTEGER FUNCTION SIFLCL(FD)

        Input  Arguments:
        -----------------
               FD     (Integer):       FILE *

        Output Arguments:
        -----------------
               None
  
        Function   Value:
        -----------------
               SIFLCL (Integer):       0   Success
                                       -1  Generic Failure
  

SIFLOP routine

This routine open a C language stream file. Accepts an integer and two character string arguments:
[1]: integer to contain a FILE *.                         
[2]: The file name                          
[3]: The I/O mode, e.g. 'r', 'w', 'w+', 'rw'                               

See `man fopen' or VAX C RTL equivalent.
This routine is in the file SIFILEOPS.C.

	INTEGER FUNCTION SIFLOP(FD,FILENAME,FILEMODE)

        Input  Arguments:
        -----------------
               FILENAME  (Character):    File name
               FILEMODE  (Character):    File access mode

        Output Arguments:
        -----------------
               FD        (Integer):      FILE *

        Function   Value:
        -----------------
               SIFLOP    (Integer):      0   Success
                                         -1  Generic Failure

SIFLRD routine

This routine reads from stream file into a buffer. Accepts the following areguments:
                          
[1]: integer containing a FILE *.
[2]: buffer area (not a character string)
[3]: integer record length expected
[4]: integer to contain amount actually read
[5]: integer: 0 for fread, 1 for fgets

This routine is in the file SIFILEOPS.C.

	INTEGER FUNCTION SIFLRD(FD,BUFFER,LRECL,NDAT,MODE)

        Input  Arguments:
        ----------------
               FD         (Integer):     FILE *
               BUFFER     (Character):   buffer area (not a character string)
               LRECL      (Integer):     amount to be read
               MODE       (Integer):     mode: 0 - fread, 1 - fgets

        Output Arguments:
        ----------------
               NDAT       (Integer):      amount actually read in characters

        Function  Value:
        ----------------
               SIFLRD     (Integer):      0   Success
                                          -1  Generic Failure

SIFLSH routine

This routine flush a C language stream file. Accepts an integer:
[1]: integer containing a FILE *.

This routine is in the file SIFILEOPS.C.

	INTEGER FUNCTION SIFLSH(FD)

        Input  Arguments:
        ----------------
               FD         (Integer)       FILE *

        Output Arguments:
        ----------------
               None

        Function  Value:
        ----------------
               SIFLSH     (Integer)       0   Success

SIFLWT routine

This routine write to stream file from a buffer. Accepts the following arguments:
[1]: integer containing a FILE *.
[2]: buffer area (not a character string)
     Use %REF(character_string)
[3]: integer record length to be written
[4]: integer to contain amount actually written
     less line termination for fputs mode.
[5]: integer: 0 for fwrite, 1 for fputs
This routine is in the file SIFILEOPS.C.
       INTEGER FUNCTION SIFLWT(FD,BUFFER,LRECL,NDAT,MODE)

       Input  Arguments:
       ----------------
              FD          (Integer):      FILE *
              BUFFER      (Character):    buffer area (not a character string)
              LRECL       (Integer):      amount to be written
              MODE        (Integer):      mode: 0 - fwrite, 1 - fputs
              
        Output Arguments:
        ----------------
              NDAT        (Integer)       amount actually written in characters

        Function  Value:
        ----------------
              SIFLWT      (Integer)       0   Success
                                          -1  Generic Failure


SIFSIZ routine

This routine determine the current size of a C language stream file. Accepts an integer:
[1]: integer containing a FILE *.

This routine is in the file SINFILEOPS.C.

	INTEGER FUNCTION SIFSIZ(FD)

        Input  Arguments:
        ----------------
               FD         (Integer)       FILE *

        Output Arguments:
        ----------------
               None

        Function  Value:
        ----------------
               SIFSIZ     (Integer)       >=0 Success
                                          -1  Generic Failure
                                          Usually means no file

SIGPID routine

This routine returns an integer which is the process or other operating system work unit identifier.It is in the file SIGPID.C.

       INTEGER FUNCTION SIGPID(PROCESS_IDENTIFIER) 

        Input  Arguments:
        ----------------
               None

        Output Arguments:
        ----------------
          PROCESS_IDENTIFIER (Integer): This is the process identifier
					returned by the routine

	Function Value:
	---------------
		SISUCC		Success

SIGTIP routine

This routine returns an integer which is the Internet address of the machine of the calling process in machine byte order. This function is only implemented for UNIX systems. It is in the file SIGTIP.C.

       INTEGER FUNCTION SIGTIP(ADDRESS) 

        Input  Arguments:
        ----------------
               None

        Output Arguments:
        ----------------
          ADDRESS (Integer): This is Internet IP address of the machine

	Function Value:
	---------------
		SISUCC		Success
		SIFAIL		Failure

SIIOST routine

This subroutine interprets MIPS(SGI), RS6000(AIX), and VAX(VMS) error codes, and returns a character string.It is in the file SIIOST.CDF.

      SUBROUTINE SIIOST(IOCODE,STRING)

        Input  Arguments:
        ----------------
               IOCODE	(Integer):	Error Code

        Output Arguments:
        ----------------
               STRING (Character*(*)):	Error Message returned


SILDIR routine

This routine is a fortran callable function to get the list of directory entries matching an user supplied pattern.This routine is in the file SILDIR.C.

       INTEGER FUNCTION SILDIR(DIRNAME, PAT, FILELIST, NUMNAMES)
 
         Input  Arguments:      
         ----------------                 
                DIRNAME (Character(*)): String containing the name of 
                                        directory which we are reading.
                PAT     (Character(*)): String holding the pattern.
                FILELIST(Character(*)): User supplied array of empty strings, 
                                        of fixed size and dimension (NUMNAMES).
                NUMNAMES(Integer):      The dimension of the array.
 
         Output Arguments:     
         ----------------                 
                FILELIST(Character(*)): The list of directory entries that 
                                        match the pattern (size NUMNAMES).
                NUMNAMES(Integer):      The number of such a directory entries.
   
         Function Value:
         --------------              
                SISUCC:                 If the directory has been successfully 
                                        read.
                SITRUN:                 If there is not enough space on the 
                                        array. The directory list has been 
                                        truncated.
                SIFAIL:                 If for any reason it is impossible to 
                                        read the directory, or if there is an 
                                        entry which size is bigger than the 
                                        fixed size of string on array.

SINACK routine

This Subprogram checks if the address of the specified Item is equal to the address of N$A. If yes, the Function returns 0 (missing argument), otherwise returns the Address of the specified Item.Thie routine is in the file NOARGLIB.CDF.

       INTEGER   FUNCTION SINACK(ITEM)

         Input  Arguments:
         ----------------
                ITEM:                   Item

         Output Arguments:
         ----------------
                None

   
         Function Value:
         --------------
               SINACK (Integer*4):     %LOC(ITEM)      Address of Item
               SIMSAR:                 Missing Argument

SIRENA routine

This subroutine renames a file (due to VAX semantics, the file should be closed).Accepts two character string arguments:
[1]: The current name for the file.
[2]: The new name for the file.
This subroutine is in the file SIFILEOPS.C.
        INTEGER FUNCTION SIRENA(OLDNAM,NEWNAM)

        Input  Arguments:
        -----------------
               OLDNAM (Character):     Old file name
               NEWNAM (Character):     New file name

        Output Arguments:
        ----------------
               None

        Function  Value:
        ----------------
               SIRENA:                 SISUCC  Success
                                       SIFAIL  Generic Failure


SIRNDX routine

This routine is fortran callable reverse index, ie. it finds the last occurance of substr in srcstr.This rutine is in the file SIRNDX.C.

      INTEGER FUNCTION SIRNDX (SRCSTR,SUBSTR,LENSRC,LENSUB)

        Input  Arguments:
        ----------------
               SRCSTR (Character):    Source string
               SUBSTR (Character):    Sub string to find
               LENSRC (Integer):      Length of srcstr string
               LENSUB (Integer):      Length of substr string
 
        Output Arguments:
        ----------------
               None
 
        Function Value:
        --------------
               SIRNDX (Integer):      Index of the begining of the last
                                      occurance of substr in stcstr
                                      0 indicates that no match found
                                      -1 indicates either source or substr
                                      has a negative length
 

SISEEK routine

This subroutine seek a C language stream file.Accepts an integer:
[1]: integer containing a FILE *.
[2]: integer containing positioning amount
[3]: integer containing positioning method
This subroutine is in the file SIFILEOPS.C.
       INTEGER FUNCTION SISEEK(FD,OFFSET,RELATIVE)

       Input  Arguments:
       ----------------
              FD      (Integer):      FILE *
              OFFSET  (Integer):      positioning amount
              RELATIVE(Integer):      method:
                                             0 -- forward from beginning
                                             1 -- from current location
                                             2 -- backwards from end

       Output Arguments:
       ----------------
             None

       Output Arguments:
       ----------------
             SISEEK   (Integer)       0   Success
                                      -1  Generic Failure

SISHUT routine

This Subroutine,as the function value, returns a standard S_I return value indicating success or failure.As the argument value, returns a integer number of seconds to shutdown time. Note, negative values are possible, value will be in range -2,000,000,000<=v<=2,000,000,000. On S_I failure return, value will be 2,000,000,000.This subroutine is in the file SISHUT.C.

        INTEGER FUNCTION SISHUT(TIMELEFT)

        Input  Arguments:
        ----------------
               None

        Output Arguments:
        ----------------
               TIMELEFT (Integer)  Array of 6 integers

        Function  Value:
        ----------------
               SISUCC		Success
	       SIFAIL		Failure

SISIZE routine

This subroutine determine the current size of a file N.B. file may need to be closed to get correct size.Accepts a character string argument:
[1]: A file name
This subroutine is in the file SIFILEOPS.C.
       INTEGER FUNCTION SISIZE(FILENAME)

       Input  Arguments:
       ----------------
              FILENAME(Character):    File name

       Output Arguments:
       ----------------
              None

       Function  Value:
       ----------------
              SISIZE  (Integer):      >=0 Success
                                      -1  Generic Failure
                                      Usually means no file

SISLEP routine

This subroutine close a C language stream file.Accepts an integer:
[1]: integer containing a number of seconds to sleep
This subroutine is in the file SIFILEOPS.C.
        INTEGER FUNCTION SISLEP(SECONDS)

        Input  Arguments:
        ----------------
               SECONDS(Integer)      Sleep time in seconds

        Output Arguments:
        ----------------
               None

        Function  Value:
        ----------------
               SISLEP (Integer)      0   Success

SISSCL routine

This routine terminate/close a connection to a remote ana client.It is in the file TPC_REMANA_SERVER.C.

      INTEGER FUNCTION SISSCL(SCH)
        
        Input  Arguments:
        ----------------
               SCH    (Integer):     Pointer socket channel Id*
        
        Output Arguments:
        ----------------
               none

        Function Value:
        --------------
               SCLOSE_SUC:           For success, or 
               SCLOSE_ERR:           For failure
 

SISSOP routine

This routine assigns a channel to then remote socket that has initiated the calling program.This routine is in the file TPC_REMANA_SERVER.C.

      INTEGER FUNCTION SISSOP(NETDCR)
        
        Input  Arguments:
        ----------------
               NETDCR (Character)
      
        Output Arguments:
        ----------------
               none
        
        Function Value:
        -------------- 
               SKOPEN_ERR:           A valid socket chan. id


SISSWT routine

This routine writes reclen bytes to the connecte socket specified by sch. This routine is in the file TPC_REMANA_SERVER.C.

        INTEGER FUNCTION SISSWT(SCH,RECLEN,BUFFER)
        
        Input  Arguments:
        -----------------
               SCH    (Integer)      Pointer to socket chan. id 
               RECLEN (Integer)      Pointer to record length in bytes 
               BUFFER (Integer)      Integer buffer reclen bytes 

        Output Arguments:
        ----------------
               None
        
        Funtion value:
        -------------
               SWRT_SUC:             For success, or 
               SWRT_ERR:             For failure.

SISTLC routine

This Subroutine converts the Source String to Lower Case and copies it to the Destination String. This routine is in the file SITRFN.CDF.


        SUBROUTINE SISTLC(DSTSTR,SRCSTR)

        Input  Arguments:
        -----------------
               SRCSTR  (Character)     Source Character String

        Output Arguments:
        ----------------
               DSTSTR  (Character)     Destination Character String

SISTLE routine

This Subroutine returns the length of the specified string, ignoring trailing spaces or tabs. This routine is in the file SITRFN.CDF.


        INTEGER FUNCTION SISTLE(STRING)

        Input  Arguments:
        -----------------
               STRING  (Character)     Character String

        Output Arguments:
        ----------------
               None

        Function  Value:
        ----------------
               SISTLE  (Integer)       Length of the string

SISTUC routine

This Subroutine converts the Source String to Upper Case and copies it to the Destination String. This routine is in the file SITRFN.CDF.


        SUBROUTINE SISTUC(DSTSTR,SRCSTR)

        Input  Arguments:
        -----------------
               SRCSTR  (Character)     Source Character String

        Output Arguments:
        ----------------
               DSTSTR  (Character)     Destination Character String


SITELL routine

This subroutine determine current position of a C language stream file.Accepts an integer:
[1]: integer containing a FILE *.
This routine is in the file SIFILEOPS.C.
        INTEGER FUNCTION SITELL(FD)
      
        Input  Arguments:
        ----------------
               FD      (Integer)       FILE *

        Output Arguments:
        ----------------
               None

        Function  Value:
        ----------------
               SITELL  (Integer)       0   Success
                                       -1  Generic Failure

SITRFN routine

This Subroutine translates a filename VAX format in the equivalent UNIX format. This routine is in the file SITRFN.CDF.

      INTEGER   FUNCTION SITRFN(VFILNAM,UFILNAM,UFILLEN)

        Input  Arguments:
        ----------------
               VFILNAM (Character):    File Name VAX Format

        Output Arguments:
        ----------------
               UFILNAM (Character):    File Name UNIX Format
               UFILLEN (Integer):      File Name UNIX Format Length

        Function Value:       
        --------------
               SITRFN                  SISUCC  Success
                                       SIINFN Invalid Filename
                                       SITRUN  Unix Filename Truncated
                                       SIFAIL  No Unix Filename

SIWAIT routine

This routine sleep a process for a given decimal time (in seconds). The minum sleep time is 1/100 of second. This routine is NOT implemented for HP-UX. This routine is in the file SIWAIT.C.

      INTEGER FUNCTION SIWAIT(SECS)

        Input  Arguments:
        ----------------
               SECS    (Real)

        Output Arguments:
        ----------------
               None

        Function Value:
        --------------
               SISUCC  (Integer):     If the required time has elapsed
               SIFAIL  (Integer):     If the required time has not elapsed for
                                      any reason.
 

SIWFSNE routine

This routine is a fortran callable function to do necessary cleanup. This routine is in the file SILDIR.C.

     INTEGER FUNCTION SIWFSNE(SEARCH)
 
        Input  Arguments:      
        ----------------          
               SEARCH  (Character(*)): String containing the name of directory 
                                       which we are reading.
 
        Output Arguments:
        ----------------
               None

        Function Value:
        --------------
               SISUCC  (Integer):     If cleanup successful
               SIFAIL  (Integer):     Otherwise
 


SIWFSNI routine

This routine is a fortran callable function to scan directory entries. This routine is in the file SILDIR.C.

      INTEGER FUNCTION SIWFSNI(SEARCH,DOTFLAG)

        Input  Arguments:      
        ----------------                         
               SEARCH  (Character(*)):String containing the name of directory 
                                      which we are reading.
               DOTFLAG                0 -> omit dot files, 1 -> include dot 
                                      file.A file is included if any of the 
                                      following are true: 
                                      a. The filename base component does not
			              start with a dot.
                                      b. The pattern base component does start 
                                      with a dot.
                                      c. The dotflag integer is nonzero.
				      This argument is ignored on OpenVMS.
 
        Output Arguments:     
        ----------------
               None 

        Function Value:
        ---------------
               SISUCC  (Integer):     If setup is successful
               SIFAIL  (Integer):     Otherwise

SIWFSNN routine

This routine is a fortran callable function to get next directory entry. This routine is in the file SILDIR.C.

      INTEGER FUNCTION SIWFSNN(RESPONSE)
            
        Input  Arguments:
        ----------------
               None

        Output Arguments:     
        ----------------
               RESPONSE               String to contain a response
 
        Function Value:
        -------------- 
               SISUCC  (Integer):     If the entry has been successfully read.
               SITRUN  (Integer):     If the entry name is longer than the 
                                      response area
               SIFAIL  (Integer):     If for any reason it is impossible to 
                                      read a entry

STRUPC routine

This subroutine is an IBM version string to upper case. This routine is in the file STRUPC.CDF.

      SUBROUTINE STRUPC(OUSTRG,INSTRG)

        Input  Arguments:
        ----------------
               INSTRG  (Character(*)): Input string to upper case.
 
        Output Arguments:
        ----------------
               OUSTRG  (Character(*)): Output string.

SUMTIM routine

This subroutine calculates timing statistics from common TIMSTA and outputs summary to logical unit LUNIT. This routine is in the file SUMTIM.CDF.

      SUBROUTINE SUMTIM(LUNIT)
 
        Input  Arguments:
        ----------------
               LUNIT  (Logical):    Logical unit number for timing summary

        Output Arguments:
        ----------------
               None

TRNLOG routine

This subroutine translates an entry in the logical name table which associates a specified logical name with an equivalence name. The translation process is iterated until the previous translation has no logical translation itself. This process is repeated a maximum of 10 times.

      SUBROUTINE TRNLOG(LGCLNM,TRANSL,IERROR)

        Input Arguments:
        ---------------
              LGCLNM   (Character(*)):Logical name to be translated.
                                      Max of 132 characters in length.

        Output Arguments:
        ----------------
              TRANSL   (Character(*)):Translation.
                                      Max of 132 characters in length.

              IERROR   (Integer*4):   Error code as defined in C$INC:ERLEVL.
                                      INC.

UP1TIM routine

This subroutine update timing statistics for specified block of code. This routine should be called just before the code block is to be executed. This routine is in the file UP1TIM.CDF.

      SUBROUTINE UP1TIM(NAM)

        Input Arguments:
        ---------------
              NAM      (Character):   Char string labeling code block to be 
                                      timed (20 or less char)

    
        Output Arguments:
        ----------------
               None

UP2TIM routine

This subroutine update timing statistics for specified block of code. This routine should be called just after the code block has been executed. The CPU time between this call and the last call to UP1TIM(NAM) will be used to update the timing stats for code block 'NAM'. This routine is in the file UP2TIM.CDF.

      SUBROUTINE UP2TIM(NAM)

        Input  Arguments:
        ---------------
               NAM      (Character):   Char string labeling code block to be 
                                       timed (20 or less char)
            
        Output Arguments:
        ----------------
               None

ZPRINT routine

This routine is a logical function that is used to control diagnostic print output in the simulation. In normal operation, ZPRINT is .FALSE. This subroutine is modified by the user to enable or disable print output as he wishes. This file is an example of how it might be set up. This routine is in the file ZPRINT.CDF.

      LOGICAL FUNCTION ZPRINT(IUSER,LEVEL)

        Input Arguments:
        ---------------      
              IUSER     (Character):  Variable specifying the location or type 
                                      of print diagnostic
              LEVEL     (Integer):    Variable specifying the diagnostic level
                                      of the print statement

        Output Arguments:
        ----------------
               None

        Function  Value:
        ----------------
               ZPRINT               .TRUE. to cause printing of the statement


Many thanks to M. Giovanna Stomeo (Flavia's cusin) for working hard to make this document available while learning HTML.