C
C Program INV1SOFT to evaluate the coefficients of the soft subjective
C a priori information on the perturbations of the model parameters.
C The subjective a priori information is composed of the squares of the
C Sobolev norms of the functions describing the model.
C
C Version: 5.10
C Date: 1997, September 30
C
C Coded by: Ludek Klimes
C     Department of Geophysics, Charles University Prague,
C     Ke Karlovu 3, 121 16 Praha 2, Czech Republic,
C     E-mail: klimes@seis.karlov.mff.cuni.cz
C
C.......................................................................
C
C Program INV1SOFT assumes all model parameters (coefficients) stored in
C the common block /VALC/ as in the submitted versions of user-defined
C model specification FORTRAN77 source code files 'srfc.for', 'parm.for',
C and 'val.for'.  Thus, unlike the other parts of the complete ray
C tracing, the INV1SOFT program cannot work with user's modifications of
C the subroutines SRFC1, SRFC2, PARM1, and PARM2.
C
C.......................................................................
C
C                                                    
C Description of data files:
C
C     All data are read in by the list directed input (free format).
C     In the lists of input data below, each numbered paragraph
C     indicates the beginning of a new input operation (new READ
C     statement).
C     The CHARACTER strings are denoted by symbolic names enclosed in
C     apostrophes.  Otherwise, if the first letter of the symbolic name
C     of the input variable is I-N, the corresponding value in input
C     data must be of the type INTEGER.  Otherwise, the input parameter
C     is of the type REAL.
C     The first 80 characters of the strings are significant.
C
C Main input data file read from the interactive device (*):
C (1) 'MODEL','INV1SOFT','SOFT',/
C     'MODEL'... String containing the name of the input data file
C             specifying the model.  For description of the data file
C             refer to file 'model.for' of package MODEL.
C             Description of file MODEL
C     'INV1SOFT'... String containing the name of the input data file
C             containing the coefficients describing the Sobolev scalar
C             product under consideration.
C             Description of file INV1SOFT
C     'SOFT'..String containing the name of the output file containing
C             the subjective prior information.
C             The structure of the file is described below.
C             Description of file SOFT
C     /...    An obligatory slash at the end of line to enable for
C             future extensions.
C     Default: 'MODEL'='model.dat', 'INV1SOFT'='soft.dat',
C             'SOFT'='soft.out'.
C
C                                                
C Input data INV1SOFT:
C     This data file contains the coefficients describing the Sobolev
C     scalar product under consideration.
C (1) (NW1(I),NW2(I),NW3(I),I=1,NW),/
C     List of partial derivatives included in the Sobolev scalar product
C     which is assumed to represent subjective prior information about
C     the model, terminated by a slash.
C     NW1,NW2,NW3... Orders of partial derivatives with respect to
C             X1,X2,X3 coordinates.  For (bi-,tri-)cubic splines, the
C             third homogeneous partial derivatives are discontinuous.
C             NWi thus should not exceed 3, allowing for 64 different
C             partial derivatives at the most.
C (2) ((WCS(I,J),I=1,J),J=1,NW)
C     Elements of the constant symmetric weighting matrix of the Sobolev
C     scalar product.
C     WCS(I,J)... Coefficient of the product of
C             (NW1(I),NW2(I),NW3(I))-th and (NW1(J),NW2(J),NW3(J))-th
C             partial derivatives of functions in the Sobolev scalar
C             product.  The product of the derivatives is integrated
C             over the volume (surface, length) of the spline grid and
C             divided by the volume (surface, length) of the grid to
C             yield the average value of the product of the derivatives,
C             The average value is multiplied by WCS(I,J) to form the
C             contribution to the Sobolev scalar product.
C Example of data INV1SOFT
C
C                                                    
C Output file SOFT:
C (1) NM
C     NM...   Number of model parameters considered by this program.
C (2) (INDM(I),I=1,NM)
C     INDM... Indices of the model parameters considered by this
C             program.  The indices correspond to the relative location
C             in the memory, in array RPAR of common block /VALC/.
C             B-spline coefficients are listed in the same order as the
C             grid velocities in file MODEL.
C             Common block /VALC/
C (3) (RS(I),I=1,NM)
C     RS...   Parameters (coefficients) of the initial (input) model.
C (4) ((CS(I,J),I=1,J),J=1,NM):
C     CS...   Relative inverse subjective prior information covariance
C             matrix.  Note that subjective data are assumed to be minus
C             the above initial model parameters, and the matrix GS
C             projecting the perturbations of model parameters onto the
C             subjective data is assumed to be identity.
C             Matrix CS is the symmetric matrix of the Sobolev scalar
C             products of the basis functions corresponding to the model
C             parameters.
C
C-----------------------------------------------------------------------
C
C Common block /VALC/:
      INCLUDE 'val.inc'
C     val.inc
C None of the storage locations of the common block are altered.
C
C Common block /RAMC/:
      INCLUDE 'ram.inc'
C     ram.inc
      INTEGER IRAM(MRAM)
      EQUIVALENCE (RAM,IRAM)
C
C-----------------------------------------------------------------------
C
C     Filenames:
      CHARACTER*80 FMODEL,FINV1,FSOFT
C
C     Logical unit number:
      INTEGER LU1
      PARAMETER (LU1=1)
C
      INTEGER NW,NM
C     NW...   Number of specified partial derivatives.
C     NM...   Number of the unknown model parameters.
C
C     Addresses in array RAM:
      INTEGER IWCS0,INDM0,ICS0,IB0
C     IRAM(1:3),IRAM(4:6),...,IRAM(3*NW-2:3*NW)... Orders of partial
C             derivatives.
C     IWCS0=3*NW... Origin of array WCS(I,J) of the weights describing
C             the Sobolev scalar product.
C     INDM0=IWCS0+NW*(NW+1)/2... Origin of array INDM of the indices of
C             model parameters.
C     ICS0=INDM0+NM... Origin of symmetric matrix CS of the Sobolev
C             scalar products of the basis functions corresponding to
C             the model parameters.
C     IB0=ICS0+NM*(NM+1)/2
C
      INTEGER MW,I,J
      REAL WEIGHT
C
C.......................................................................
C
C     Opening data files and reading the input data:
C
C     Main input data file read from the interactive device (*):
      WRITE(*,'(A)') ' Enter the names of files MODEL, INV1SOFT, SOFT: '
      FMODEL='model.dat'
      FINV1='soft.dat'
      FSOFT='soft.out'
      READ(*,*) FMODEL,FINV1,FSOFT
      WRITE(*,'(A)') '+                                                '
C
C     Input data MODEL for the model:
      OPEN(LU1,FILE=FMODEL,STATUS='OLD')
      CALL MODEL1(LU1)
      CLOSE(LU1)
C
C     Number of unknown model parameters:
      CALL SOFT(2,0,0,0,0,0,0,0.,NM,IRAM,RAM,1,RAM)
C     (We have just hoped here that array RAM is sufficiently large.)
C     WRITE(*,'(A,I4,A)') '+',NM,' model parameters'
C
C     Input data INV1SOFT:
      OPEN(LU1,FILE=FINV1,STATUS='OLD')
C     Reading prior subjective information coefficients:
C     Maximum number MW of different partial derivatives
      MW=MIN0(64,(MRAM-1)/3)
      DO 21 I=1,3*MW+1
        IRAM(I)=-1
   21 CONTINUE
      READ(LU1,*) (IRAM(I),I=1,3*MW+1)
      DO 22 I=1,MW+1
        IF(IRAM(I).LT.0) THEN
          NW=(I-1)/3
          IF(3*NW.NE.I-1) THEN
C           INV1SOFT-01
            PAUSE 'Error INV1SOFT-01: Wrong partial derivatives'
            STOP
C           The input partial derivatives do not form triplets,
C           or some of the derivatives is of a negative order.
          END IF
          GO TO 23
        END IF
   22 CONTINUE
C       INV1SOFT-02
        PAUSE 'Error INV1SOFT-02: Too many partial derivatives'
        STOP
C       The number of input triplets of partial derivatives is greater
C       than the maximum number MW defined few lines above.
   23 CONTINUE
      IWCS0=3*NW
      INDM0=IWCS0+NW*(NW+1)/2
      ICS0=INDM0+NM
      IB0=ICS0+NM*(NM+1)/2
      IF(IB0.GE.MRAM) THEN
C       INV1SOFT-03
        PAUSE 'Error INV1SOFT-03: Too small array RAM'
        STOP
C       Dimension MRAM of array RAM in include file
C       ram.inc
C       should be increased to accommodate the input coefficients of the
C       Sobolev scalar product and the output symmetric matrix CS of the
C       Sobolev scalar products of the basis functions corresponding to
C       the model parameters.
      END IF
      READ(LU1,*) (RAM(I),I=IWCS0+1,INDM0)
      CLOSE(LU1)
C
C.......................................................................
C
C     Opening output file:
      OPEN(LU1,FILE=FSOFT)
      I=MAX0(INDEX(FSOFT,'          ')-1,11)
      WRITE(*,'('' Generating the output: '',A)') FSOFT(1:I)
C
C     Generating prior subjective information covariance matrix:
      DO 41 I=ICS0+1,IB0
        RAM(I)=0.
   41 CONTINUE
      DO 49 J=1,NW
        DO 48 I=1,J
          WEIGHT=RAM(IWCS0+J*(J-1)/2+I)
          IF(WEIGHT.NE.0.) THEN
            CALL SOFT(2,IRAM(3*I-2),IRAM(3*I-1),IRAM(3*I),
     *                  IRAM(3*J-2),IRAM(3*J-1),IRAM(3*J),WEIGHT,
     *                NM,IRAM(INDM0+1),RAM(ICS0+1),MRAM-IB0,RAM(IB0+1))
          END IF
   48   CONTINUE
   49 CONTINUE
C
C     (1,2,3) Writing the initial model parameters INDM:
      WRITE(LU1,'(I8)')           NM
      WRITE(LU1,'(I8,5I13)')      (IRAM(I),I=INDM0+1,INDM0+NM)
      WRITE(LU1,'(6(G12.6,1X))')  (RPAR(IRAM(I)),I=INDM0+1,INDM0+NM)
      WRITE(LU1,'(6(G12.6,1X))')
C
C     (4) Writing the prior subjective information covariance matrix CS:
      DO 90 J=1,NM
        WRITE(LU1,'(6(G12.6,1X))')
     *                        (RAM(I),I=ICS0+J*(J-1)/2+1,ICS0+J*(J+1)/2)
   90 CONTINUE
      CLOSE(LU1)
C
      STOP
      END
C
C=======================================================================
C
      INCLUDE 'model.for'
C     model.for
      INCLUDE 'metric.for'
C     metric.for
      INCLUDE 'srfc.for'
C     srfc.for
      INCLUDE 'parm.for'
C     parm.for
      INCLUDE 'val.for'
C     val.for
      INCLUDE 'fit.for'
C     fit.for
      INCLUDE 'spsp.for'
C     spsp.for
      INCLUDE 'soft.for'
C     soft.for
C
C=======================================================================
C