| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285 | *DECK SSGS      SUBROUTINE SSGS (N, B, X, NELT, IA, JA, A, ISYM, ITOL, TOL, ITMAX,     +   ITER, ERR, IERR, IUNIT, RWORK, LENW, IWORK, LENIW)C***BEGIN PROLOGUE  SSGSC***PURPOSE  Gauss-Seidel Method Iterative Sparse Ax = b Solver.C            Routine to solve a general linear system  Ax = b  usingC            Gauss-Seidel iteration.C***LIBRARY   SLATEC (SLAP)C***CATEGORY  D2A4, D2B4C***TYPE      SINGLE PRECISION (SSGS-S, DSGS-D)C***KEYWORDS  ITERATIVE PRECONDITION, LINEAR SYSTEM, SLAP, SPARSEC***AUTHOR  Greenbaum, Anne, (Courant Institute)C           Seager, Mark K., (LLNL)C             Lawrence Livermore National LaboratoryC             PO BOX 808, L-60C             Livermore, CA 94550 (510) 423-3141C             seager@llnl.govC***DESCRIPTIONCC *Usage:C     INTEGER N, NELT, IA(NELT), JA(NELT), ISYM, ITOL, ITMAXC     INTEGER ITER, IERR, IUNIT, LENW, IWORK(NL+2*N+1), LENIWC     REAL B(N), X(N), A(NELT), TOL, ERR, RWORK(NL+3*N)CC     CALL SSGS(N, B, X, NELT, IA, JA, A, ISYM, ITOL, TOL,C    $     ITMAX, ITER, ERR, IERR, IUNIT, RWORK, LENW, IWORK, LENIW )CC *Arguments:C N      :IN       Integer.C         Order of the Matrix.C B      :IN       Real B(N).C         Right-hand side vector.C X      :INOUT    Real X(N).C         On input X is your initial guess for solution vector.C         On output X is the final approximate solution.C NELT   :IN       Integer.C         Number of Non-Zeros stored in A.C IA     :INOUT    Integer IA(NELT).C JA     :INOUT    Integer JA(NELT).C A      :INOUT    Real A(NELT).C         These arrays should hold the matrix A in either the SLAPC         Triad format or the SLAP Column format.  See "Description",C         below.  If the SLAP Triad format is chosen it is changedC         internally to the SLAP Column format.C ISYM   :IN       Integer.C         Flag to indicate symmetric storage format.C         If ISYM=0, all non-zero entries of the matrix are stored.C         If ISYM=1, the matrix is symmetric, and only the lowerC         lower triangle of the matrix is stored.C ITOL   :IN       Integer.C         Flag to indicate type of convergence criterion.C         If ITOL=1, iteration stops when the 2-norm of the residualC         divided by the 2-norm of the right-hand side is less than TOL.C         If ITOL=2, iteration stops when the 2-norm of M-inv times theC         residual divided by the 2-norm of M-inv times the right handC         side is less than TOL, where M-inv is the inverse of theC         diagonal of A.C         ITOL=11 is often useful for checking and comparing differentC         routines.  For this case, the user must supply the "exact"C         solution or a very accurate approximation (one with an errorC         much less than TOL) through a common block,C             COMMON /SSLBLK/ SOLN( )C         If ITOL=11, iteration stops when the 2-norm of the differenceC         between the iterative approximation and the user-suppliedC         solution divided by the 2-norm of the user-supplied solutionC         is less than TOL.  Note that this requires the user to set upC         the "COMMON /SSLBLK/ SOLN(LENGTH)" in the calling routine.C         The routine with this declaration should be loaded before theC         stop test so that the correct length is used by the loader.C         This procedure is not standard Fortran and may not workC         correctly on your system (although it has worked on everyC         system the authors have tried).  If ITOL is not 11 then thisC         common block is indeed standard Fortran.C TOL    :INOUT    Real.C         Convergence criterion, as described above.  (Reset if IERR=4.)C ITMAX  :IN       Integer.C         Maximum number of iterations.C ITER   :OUT      Integer.C         Number of iterations required to reach convergence, orC         ITMAX+1 if convergence criterion could not be achieved inC         ITMAX iterations.C ERR    :OUT      Real.C         Error estimate of error in final approximate solution, asC         defined by ITOL.C IERR   :OUT      Integer.C         Return error flag.C           IERR = 0 => All went well.C           IERR = 1 => Insufficient space allocated for WORK or IWORK.C           IERR = 2 => Method failed to converge in ITMAX steps.C           IERR = 3 => Error in user input.C                       Check input values of N, ITOL.C           IERR = 4 => User error tolerance set too tight.C                       Reset to 500*R1MACH(3).  Iteration proceeded.C           IERR = 5 => Preconditioning matrix, M, is not positiveC                       definite.  (r,z) < 0.C           IERR = 6 => Matrix A is not positive definite.  (p,Ap) < 0.C IUNIT  :IN       Integer.C         Unit number on which to write the error at each iteration,C         if this is desired for monitoring convergence.  If unitC         number is 0, no writing will occur.C RWORK  :WORK     Real RWORK(LENW).C         Real array used for workspace.C LENW   :IN       Integer.C         Length of the real workspace, RWORK.  LENW >= NL+3*N.C         NL is the number of non-zeros in the lower triangle of theC         matrix (including the diagonal).C IWORK  :WORK     Integer IWORK(LENIW).C         Integer array used for workspace.C         Upon return the following locations of IWORK hold informationC         which may be of use to the user:C         IWORK(9)  Amount of Integer workspace actually used.C         IWORK(10) Amount of Real workspace actually used.C LENIW  :IN       Integer.C         Length of the integer workspace, IWORK.  LENIW >= NL+N+11.C         NL is the number of non-zeros in the lower triangle of theC         matrix (including the diagonal).CC *DescriptionC       The Sparse Linear Algebra Package (SLAP) utilizes two matrixC       data structures: 1) the  SLAP Triad  format or  2)  the SLAPC       Column format.  The user can hand this routine either of theC       of these data structures and SLAP  will figure out  which onC       is being used and act accordingly.CC       =================== S L A P Triad format ===================CC       This routine requires that the  matrix A be   stored in  theC       SLAP  Triad format.  In  this format only the non-zeros  areC       stored.  They may appear in  *ANY* order.  The user suppliesC       three arrays of  length NELT, where  NELT is  the number  ofC       non-zeros in the matrix: (IA(NELT), JA(NELT), A(NELT)).  ForC       each non-zero the user puts the row and column index of thatC       matrix element  in the IA and  JA arrays.  The  value of theC       non-zero   matrix  element is  placed  in  the correspondingC       location of the A array.   This is  an  extremely  easy dataC       structure to generate.  On  the  other hand it   is  not tooC       efficient on vector computers for  the iterative solution ofC       linear systems.  Hence,   SLAP changes   this  input    dataC       structure to the SLAP Column format  for  the iteration (butC       does not change it back).CC       Here is an example of the  SLAP Triad   storage format for aC       5x5 Matrix.  Recall that the entries may appear in any order.CC           5x5 Matrix      SLAP Triad format for 5x5 matrix on left.C                              1  2  3  4  5  6  7  8  9 10 11C       |11 12  0  0 15|   A: 51 12 11 33 15 53 55 22 35 44 21C       |21 22  0  0  0|  IA:  5  1  1  3  1  5  5  2  3  4  2C       | 0  0 33  0 35|  JA:  1  2  1  3  5  3  5  2  5  4  1C       | 0  0  0 44  0|C       |51  0 53  0 55|CC       =================== S L A P Column format ==================CC       This routine  requires that  the matrix A  be stored in  theC       SLAP Column format.  In this format the non-zeros are storedC       counting down columns (except for  the diagonal entry, whichC       must appear first in each  "column")  and are stored  in theC       real array A.  In other words, for each column in the matrixC       put the diagonal entry in A.  Then put in the other non-zeroC       elements going down   the  column (except  the diagonal)  inC       order.  The IA array holds the row  index for each non-zero.C       The JA array holds the offsets into the IA, A arrays for theC       beginning of   each    column.    That  is,    IA(JA(ICOL)),C       A(JA(ICOL)) points to the beginning of the ICOL-th column inC       IA and  A.  IA(JA(ICOL+1)-1),  A(JA(ICOL+1)-1) points to theC       end  of   the ICOL-th  column.  Note   that  we  always haveC       JA(N+1) = NELT+1, where  N  is the number of columns in  theC       matrix and  NELT   is the number of non-zeros in the matrix.CC       Here is an example of the  SLAP Column  storage format for aC       5x5 Matrix (in the A and IA arrays '|'  denotes the end of aC       column):CC           5x5 Matrix      SLAP Column format for 5x5 matrix on left.C                              1  2  3    4  5    6  7    8    9 10 11C       |11 12  0  0 15|   A: 11 21 51 | 22 12 | 33 53 | 44 | 55 15 35C       |21 22  0  0  0|  IA:  1  2  5 |  2  1 |  3  5 |  4 |  5  1  3C       | 0  0 33  0 35|  JA:  1  4  6    8  9   12C       | 0  0  0 44  0|C       |51  0 53  0 55|CC *Side Effects:C       The SLAP Triad format (IA, JA, A) is modified internally to beC       the SLAP Column format.  See above.CC *Cautions:C     This routine will attempt to write to the Fortran logical outputC     unit IUNIT, if IUNIT .ne. 0.  Thus, the user must make sure thatC     this logical unit is attached to a file or terminal before callingC     this routine with a non-zero value for IUNIT.  This routine doesC     not check for the validity of a non-zero IUNIT unit number.CC***SEE ALSO  SSJAC, SIRC***REFERENCES  (NONE)C***ROUTINES CALLED  SCHKW, SIR, SS2LT, SS2Y, SSLI, SSMVC***REVISION HISTORY  (YYMMDD)C   871119  DATE WRITTENC   881213  Previous REVISION DATEC   890915  Made changes requested at July 1989 CML Meeting.  (MKS)C   890921  Removed TeX from comments.  (FNF)C   890922  Numerous changes to prologue to make closer to SLATECC           standard.  (FNF)C   890929  Numerous changes to reduce SP/DP differences.  (FNF)C   910411  Prologue converted to Version 4.0 format.  (BAB)C   920407  COMMON BLOCK renamed SSLBLK.  (WRB)C   920511  Added complete declaration section.  (WRB)C   921019  Corrected NEL to NL.  (FNF)C***END PROLOGUE  SSGSC     .. Parameters ..      INTEGER LOCRB, LOCIB      PARAMETER (LOCRB=1, LOCIB=11)C     .. Scalar Arguments ..      REAL ERR, TOL      INTEGER IERR, ISYM, ITER, ITMAX, ITOL, IUNIT, LENIW, LENW, N, NELTC     .. Array Arguments ..      REAL A(N), B(N), RWORK(*), X(N)      INTEGER IA(NELT), IWORK(10), JA(NELT)C     .. Local Scalars ..      INTEGER ICOL, J, JBGN, JEND, LOCDZ, LOCEL, LOCIEL, LOCIW, LOCJEL,     +        LOCR, LOCW, LOCZ, NLC     .. External Subroutines ..      EXTERNAL SCHKW, SIR, SS2LT, SS2Y, SSLI, SSMVC***FIRST EXECUTABLE STATEMENT  SSGSC      IF( N.LT.1 .OR. NELT.LT.1 ) THEN         IERR = 3         RETURN      ENDIFCC         Modify the SLAP matrix data structure to YSMP-Column.      CALL SS2Y( N, NELT, IA, JA, A, ISYM )CC         Count number of elements in lower triangle of the matrix.      IF( ISYM.EQ.0 ) THEN         NL = 0         DO 20 ICOL = 1, N            JBGN = JA(ICOL)            JEND = JA(ICOL+1)-1            DO 10 J = JBGN, JEND               IF( IA(J).GE.ICOL ) NL = NL + 1 10         CONTINUE 20      CONTINUE      ELSE         NL = JA(N+1)-1      ENDIFCC         Set up the work arrays.  Then store the lower triangle ofC         the matrix.C      LOCJEL = LOCIB      LOCIEL = LOCJEL + N+1      LOCIW = LOCIEL + NLC      LOCEL = LOCRB      LOCR = LOCEL + NL      LOCZ = LOCR + N      LOCDZ = LOCZ + N      LOCW = LOCDZ + NCC         Check the workspace allocations.      CALL SCHKW( 'SSGS', LOCIW, LENIW, LOCW, LENW, IERR, ITER, ERR )      IF( IERR.NE.0 ) RETURNC      IWORK(1) = NL      IWORK(2) = LOCIEL      IWORK(3) = LOCJEL      IWORK(4) = LOCEL      IWORK(9) = LOCIW      IWORK(10) = LOCWC      CALL SS2LT( N, NELT, IA, JA, A, ISYM, NL, IWORK(LOCIEL),     $     IWORK(LOCJEL), RWORK(LOCEL) )CC         Call iterative refinement routine.      CALL SIR(N, B, X, NELT, IA, JA, A, ISYM, SSMV, SSLI,     $     ITOL, TOL, ITMAX, ITER, ERR, IERR, IUNIT, RWORK(LOCR),     $     RWORK(LOCZ), RWORK(LOCDZ), RWORK, IWORK )CC         Set the amount of Integer and Real Workspace used.      IWORK(9) = LOCIW+N+NELT      IWORK(10) = LOCW+NELT      RETURNC------------- LAST LINE OF SSGS FOLLOWS ------------------------------      END
 |