SLATEC Routines --- DCOEF ---


*DECK DCOEF
      SUBROUTINE DCOEF (YH, YP, NCOMP, NROWB, NFC, NIC, B, BETA, COEF,
     +   INHOMO, RE, AE, BY, CVEC, WORK, IWORK, IFLAG, NFCC)
C***BEGIN PROLOGUE  DCOEF
C***SUBSIDIARY
C***PURPOSE  Subsidiary to DBVSUP
C***LIBRARY   SLATEC
C***TYPE      DOUBLE PRECISION (SCOEF-S, DCOEF-D)
C***AUTHOR  Watts, H. A., (SNLA)
C***DESCRIPTION
C
C **********************************************************************
C INPUT to DCOEF
C **********************************************************************
C
C     YH = matrix of homogeneous solutions.
C     YP = vector containing particular solution.
C     NCOMP = number of components per solution vector.
C     NROWB = first dimension of B in calling program.
C     NFC = number of base solution vectors.
C     NFCC = 2*NFC for the special treatment of COMPLEX*16 valued
C            equations. Otherwise, NFCC=NFC.
C     NIC = number of specified initial conditions.
C     B = boundary condition matrix at X = XFINAL.
C     BETA = vector of nonhomogeneous boundary conditions at X = XFINAL.
C              1 - nonzero particular solution
C     INHOMO = 2 - zero particular solution
C              3 - eigenvalue problem
C     RE = relative error tolerance.
C     AE = absolute error tolerance.
C     BY = storage space for the matrix  B*YH
C     CVEC = storage space for the vector  BETA-B*YP
C     WORK = double precision array of internal storage. Dimension must
C     be GE
C            NFCC*(NFCC+4)
C     IWORK = integer array of internal storage. Dimension must be GE
C             3+NFCC
C
C **********************************************************************
C OUTPUT from DCOEF
C **********************************************************************
C
C     COEF = array containing superposition constants.
C     IFLAG = indicator of success from DSUDS in solving the
C             boundary equations.
C           = 0 boundary equations are solved.
C           = 1 boundary equations appear to have many solutions.
C           = 2 boundary equations appear to be inconsistent.
C           = 3 for this value of an eigenparameter, the boundary
C               equations have only the zero solution.
C
C **********************************************************************
C
C     Subroutine DCOEF solves for the superposition constants from the
C     linear equations defined by the boundary conditions at X = XFINAL.
C
C                          B*YP + B*YH*COEF = BETA
C
C **********************************************************************
C
C***SEE ALSO  DBVSUP
C***ROUTINES CALLED  DDOT, DSUDS, XGETF, XSETF
C***COMMON BLOCKS    DML5MC
C***REVISION HISTORY  (YYMMDD)
C   750601  DATE WRITTEN
C   890531  Changed all specific intrinsics to generic.  (WRB)
C   890831  Modified array declarations.  (WRB)
C   890921  Realigned order of variables in certain COMMON blocks.
C           (WRB)
C   890921  REVISION DATE from Version 3.2
C   891214  Prologue converted to Version 4.0 format.  (BAB)
C   900328  Added TYPE section.  (WRB)
C   910722  Updated AUTHOR section.  (ALS)
C***END PROLOGUE  DCOEF