SUBROUTINE ABQMAIN
C====================================================================
C This program must be compiled and linked with the command:
C     abaqus make job=fjoin
C Run the program using the command:
C     abaqus fjoin
C====================================================================
C
C  Purpose (this program performs two functions): 
C 
C 1. It can be used to join together a number of ABAQUS results files. 
C    The program will prompt the user for the number of files to be 
C    joined, the FORTRAN unit numbers associated with each file and   
C    the file format, ASCII or binary.  The user will also be prompted
C    for the format of the output file and the root name of the files.
C
C 2. It can be used to convert the format of a file from binary to 
C    ASCII or vice-versa.  This can be accomplished by reading one 
C    file as input and giving the opposite format for the output file.
C
C  Input File names:
C
C    The results file to be processed should be named 'FNAME.0xx', 
C    where xx is a 2-digit FORTRAN unit number less than 31.  
C    Certain units within this range are used by ABAQUS internally and
C    by this program and cannot be used by the user.  These are 01, 
C    05, 06, 07, 09, 11, 12, 13, 20 and 28.
C
C  Output File name: 
C
C    'FNAME'.fin
C
C====================================================================
C
C  Variables used by this program:
C
C   ARRAY  -- Real array containing values read from results file
C               (.fil). Equivalenced to JRRAY.
C   JRRAY  -- Integer array containing values read from results file
C               (.fil). Equivalenced to ARRAY.
C   FNAME  -- Root file name of input file(s) and output file.
C   NRU    -- Number of results files (.fil) to be read.
C   LRUNIT -- Array containing unit number and format of results files:
C               LRUNIT(1,*) --> Unit number of input file.
C               LRUNIT(2,*) --> Format of input file.
C   LOUTF  -- Format of output file:
C               1 --> ABAQUS results file ASCII format.
C               2 --> ABAQUS results file binary format.
C   JUNIT  -- Unit number of file to be opened.
C   JRCD   -- Error check return code:
C               .EQ. 0 --> No errors.
C               .NE. 0 --> Errors detected.
C   KEY    -- Current record key identifier.
C
C====================================================================
C
C  The use of ABA_PARAM.INC eliminates the need to have different
C  versions of the code for single and double precision.  
C  ABA_PARAM.INC defines an appropriate IMPLICIT REAL statement and 
C  sets the value of NPRECD to 1 or 2, depending on whether the 
C  machine uses single or double precision.  
C
C====================================================================
C
      INCLUDE 'aba_param.inc'
      DIMENSION  ARRAY(513), JRRAY(NPRECD,513)
      EQUIVALENCE (ARRAY(1), JRRAY(1,1))
C
C====================================================================
C  Set the dimensions of LRUNIT to be the maximum number of results 
C  files to be joined.
C
C====================================================================
      PARAMETER (MXUNIT=21)
      INTEGER  LRUNIT(2,MXUNIT),LUNIT(10)
      CHARACTER  FNAME*80
      DATA LUNIT/1,5,6,7,9,11,12,13,20,28/
C
C====================================================================
C  Input the number of files to be joined and then the unit number and 
C  format of each of the files.
C
C====================================================================
    5 CONTINUE
      WRITE(6,10) MXUNIT
   10 FORMAT(1X,'Enter the number of files to be joined (MAX:',I3,'):')
      READ(5,'(I3)') NRU
      IF (NRU .GT. MXUNIT) GOTO 5
C
C
      DO 40 INRU = 1, NRU
   15    CONTINUE
         WRITE(6,20) INRU
   20    FORMAT(1X,'Enter the unit number of input file #',I3,':')
         READ(5,*) LRUNIT(1,INRU)
         DO 41 K1=1,9
         IF (LRUNIT(1,INRU) .EQ. LUNIT(K1)) THEN
            WRITE(6,*) 'ERROR! Unit number cannot be ',LUNIT(K1)
            GOTO 15
         ENDIF
   41    CONTINUE 
   42    CONTINUE 
         WRITE(6,30) INRU
   30    FORMAT(1X,'Enter the format of input file #',I3,
     1             ' (1-ASCII, 2-binary):')
         READ(5,*) LRUNIT(2,INRU)
         IF (LRUNIT(2,INRU).NE. 1 .AND. LRUNIT(2,INRU) .NE. 2) THEN
             WRITE(6,*) 'ERROR! This number must be 1 or 2'
             GOTO 42
         ENDIF
   40 CONTINUE
C
C====================================================================
C  Set LOUTF equal to the format of the output file.  If this program 
C  is to be used only to convert the file format from one type to 
C  another, set NRU=1 (to read only one file) and specify a value of 
C  LOUTF which is opposite to the value specified for LRUNIT(2,1).
C
C====================================================================
   45 CONTINUE
      WRITE(6,50)
   50 FORMAT(1X,'Enter the format of the output file ',
     1          '(1-ASCII, 2-binary):')
      READ(5,*) LOUTF
      IF (LOUTF .NE. 1 .AND. LOUTF .NE. 2) THEN
            WRITE(6,*) 'ERROR! This number must be 1 or 2'
            GOTO 45
      ENDIF
C
      WRITE(6,60)
   60 FORMAT(1X,'Enter the name of the input file(s) (w/o extension):')
      READ(5,'(A)') FNAME
C
      CALL  INITPF (FNAME, NRU, LRUNIT, LOUTF)
C
      KEYPRV = 0
C
C====================================================================
C  Loop through NRU input files... 
C
C====================================================================
      DO 100 INRU = 1, NRU
         JUNIT = LRUNIT(1,INRU)
         CALL  DBRNU (JUNIT)
         I2001 = 0
C====================================================================
C  ...and cover a maximum of 10 million records in each file.
C
C====================================================================
         DO 80 IXX2 = 1, 100
         DO 80 IXX = 1, 99999
            CALL DBFILE(0,ARRAY,JRCD)
C           WRITE(6,*) 'KEY/RECORD LENGTH = ', JRRAY(1,2),JRRAY(1,1)
            IF (JRCD .NE. 0 .AND. KEYPRV .EQ. 2001) THEN
               WRITE(6,*) 'END OF FILE #', INRU
               CLOSE (JUNIT)
               GOTO 100
            ELSE IF (JRCD .NE. 0) THEN
               WRITE(6,*) 'ERROR READING FILE #', INRU
               CLOSE (JUNIT)
               GOTO 110
            ENDIF
C
C====================================================================
C  Initialize the flag to write a record to the file:
C    LWRITE=0 -- write disabled
C    LWRITE=1 -- write enabled
C
C====================================================================
           LWRITE=1
C
C====================================================================
C  For files other than the first, skip the 1900-series header records
C  except for the substructure path (1910; for substructure analyses),
C  output request (1911), heading (1922), and modal (1980; for natural
C  frequency extraction) records.  In a merged file, the heading 
C  record serves as a file delimiter.
C
C====================================================================
            IF (INRU.GT.1) THEN
               IF (JRRAY(1,2).GE.1900 .AND. JRRAY(1,2).LE.1909) LWRITE=0
               IF (JRRAY(1,2).GE.1912 .AND. JRRAY(1,2).LT.1922) LWRITE=0
C
C====================================================================
C  Skip the first 2001 record (this indicates the end of the header
C  records).
C
C====================================================================
               IF (JRRAY(1,2) .EQ. 2001 .AND. I2001 .EQ. 0) THEN
                  I2001 = 1
                  LWRITE = 0
               ENDIF
            ENDIF
C
C====================================================================
C  If this is the first input file, or if the write flag has not been 
C  disabled for records in subsequent files, then write the data to 
C  the output file.  We are interested in retrieving the header 
C  records (relevant 1900-series records), the increment start and  
C  end records (2000 and 2001), the element header record, (1) and 
C  the stress and strain records (11 and 21).
C
C====================================================================
            IF (INRU .EQ. 1 .OR. LWRITE .EQ. 1) THEN
               KEY=JRRAY(1,2)
               IF((KEY.EQ.1900).OR.(KEY.EQ.1901).OR.(KEY.EQ.1902).OR.
     1            (KEY.EQ.1910).OR.(KEY.EQ.1911).OR.(KEY.EQ.1921).OR.
     2            (KEY.EQ.1922).OR.(KEY.EQ.1980).OR.(KEY.EQ.2000).OR.
     3            (KEY.EQ.2001).OR.(KEY.EQ.1).OR.(KEY.EQ.11).OR.
     4            (KEY.EQ.21)) THEN
                 CALL DBFILW(1,ARRAY,JRCD)
                 IF (JRCD .NE. 0) THEN
                    WRITE(6,*) 'ERROR WRITING FILE'
                    CLOSE (JUNIT)
                    GOTO 110
                 ENDIF
               ENDIF
            ENDIF
            KEYPRV = JRRAY(1,2)
   80    CONTINUE
  100 CONTINUE
  110 CONTINUE
      CLOSE(9)
C
      RETURN
      END