~ubuntu-branches/ubuntu/wily/julia/wily

« back to all changes in this revision

Viewing changes to deps/openlibm/slatec/sslucs.f

  • Committer: Package Import Robot
  • Author(s): Sébastien Villemot
  • Date: 2013-01-16 12:29:42 UTC
  • mfrom: (1.1.2)
  • Revision ID: package-import@ubuntu.com-20130116122942-x86e42akjq31repw
Tags: 0.0.0+20130107.gitd9656f41-1
* New upstream snashot
* No longer try to rebuild helpdb.jl.
   + debian/rules: remove helpdb.jl from build-arch rule
   + debian/control: move back python-sphinx to Build-Depends-Indep
* debian/copyright: reflect upstream changes
* Add Build-Conflicts on libatlas3-base (makes linalg tests fail)
* debian/rules: replace obsolete USE_DEBIAN makeflag by a list of
  USE_SYSTEM_* flags
* debian/rules: on non-x86 systems, use libm instead of openlibm
* dpkg-buildflags.patch: remove patch, applied upstream
* Refreshed other patches

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
*DECK SSLUCS
 
2
      SUBROUTINE SSLUCS (N, B, X, NELT, IA, JA, A, ISYM, ITOL, TOL,
 
3
     +   ITMAX, ITER, ERR, IERR, IUNIT, RWORK, LENW, IWORK, LENIW)
 
4
C***BEGIN PROLOGUE  SSLUCS
 
5
C***PURPOSE  Incomplete LU BiConjugate Gradient Squared Ax=b Solver.
 
6
C            Routine to solve a linear system  Ax = b  using the
 
7
C            BiConjugate Gradient Squared method with Incomplete LU
 
8
C            decomposition preconditioning.
 
9
C***LIBRARY   SLATEC (SLAP)
 
10
C***CATEGORY  D2A4, D2B4
 
11
C***TYPE      SINGLE PRECISION (SSLUCS-S, DSLUCS-D)
 
12
C***KEYWORDS  ITERATIVE INCOMPLETE LU PRECONDITION,
 
13
C             NON-SYMMETRIC LINEAR SYSTEM, SLAP, SPARSE
 
14
C***AUTHOR  Greenbaum, Anne, (Courant Institute)
 
15
C           Seager, Mark K., (LLNL)
 
16
C             Lawrence Livermore National Laboratory
 
17
C             PO BOX 808, L-60
 
18
C             Livermore, CA 94550 (510) 423-3141
 
19
C             seager@llnl.gov
 
20
C***DESCRIPTION
 
21
C
 
22
C *Usage:
 
23
C     INTEGER N, NELT, IA(NELT), JA(NELT), ISYM, ITOL, ITMAX
 
24
C     INTEGER ITER, IERR, IUNIT, LENW, IWORK(NL+NU+4*N+2), LENIW
 
25
C     REAL B(N), X(N), A(NELT), TOL, ERR, RWORK(NL+NU+8*N)
 
26
C
 
27
C     CALL SSLUCS(N, B, X, NELT, IA, JA, A, ISYM, ITOL, TOL,
 
28
C    $     ITMAX, ITER, ERR, IERR, IUNIT, RWORK, LENW, IWORK, LENIW)
 
29
C
 
30
C *Arguments:
 
31
C N      :IN       Integer.
 
32
C         Order of the Matrix.
 
33
C B      :IN       Real B(N).
 
34
C         Right-hand side vector.
 
35
C X      :INOUT    Real X(N).
 
36
C         On input X is your initial guess for solution vector.
 
37
C         On output X is the final approximate solution.
 
38
C NELT   :IN       Integer.
 
39
C         Number of Non-Zeros stored in A.
 
40
C IA     :INOUT    Integer IA(NELT).
 
41
C JA     :INOUT    Integer JA(NELT).
 
42
C A      :INOUT    Real A(NELT).
 
43
C         These arrays should hold the matrix A in either the SLAP
 
44
C         Triad format or the SLAP Column format.  See "Description",
 
45
C         below.  If the SLAP Triad format is chosen it is changed
 
46
C         internally to the SLAP Column format.
 
47
C ISYM   :IN       Integer.
 
48
C         Flag to indicate symmetric storage format.
 
49
C         If ISYM=0, all non-zero entries of the matrix are stored.
 
50
C         If ISYM=1, the matrix is symmetric, and only the upper
 
51
C         or lower triangle of the matrix is stored.
 
52
C ITOL   :IN       Integer.
 
53
C         Flag to indicate type of convergence criterion.
 
54
C         If ITOL=1, iteration stops when the 2-norm of the residual
 
55
C         divided by the 2-norm of the right-hand side is less than TOL.
 
56
C         This routine must calculate the residual from R = A*X - B.
 
57
C         This is unnatural and hence expensive for this type of iter-
 
58
C         ative method.  ITOL=2 is *STRONGLY* recommended.
 
59
C         If ITOL=2, iteration stops when the 2-norm of M-inv times the
 
60
C         residual divided by the 2-norm of M-inv times the right hand
 
61
C         side is less than TOL, where M-inv time a vector is the pre-
 
62
C         conditioning step.  This is the *NATURAL* stopping for this
 
63
C         iterative method and is *STRONGLY* recommended.
 
64
C TOL    :INOUT    Real.
 
65
C         Convergence criterion, as described above.  (Reset if IERR=4.)
 
66
C ITMAX  :IN       Integer.
 
67
C         Maximum number of iterations.
 
68
C ITER   :OUT      Integer.
 
69
C         Number of iterations required to reach convergence, or
 
70
C         ITMAX+1 if convergence criterion could not be achieved in
 
71
C         ITMAX iterations.
 
72
C ERR    :OUT      Real.
 
73
C         Error estimate of error in final approximate solution, as
 
74
C         defined by ITOL.
 
75
C IERR   :OUT      Integer.
 
76
C         Return error flag.
 
77
C           IERR = 0 => All went well.
 
78
C           IERR = 1 => Insufficient space allocated for WORK or IWORK.
 
79
C           IERR = 2 => Method failed to converge in ITMAX steps.
 
80
C           IERR = 3 => Error in user input.
 
81
C                       Check input values of N, ITOL.
 
82
C           IERR = 4 => User error tolerance set too tight.
 
83
C                       Reset to 500*R1MACH(3).  Iteration proceeded.
 
84
C           IERR = 5 => Breakdown of the method detected.
 
85
C                       (r0,r) approximately 0.
 
86
C           IERR = 6 => Stagnation of the method detected.
 
87
C                       (r0,v) approximately 0.
 
88
C           IERR = 7 => Incomplete factorization broke down and was
 
89
C                       fudged.  Resulting preconditioning may be less
 
90
C                       than the best.
 
91
C IUNIT  :IN       Integer.
 
92
C         Unit number on which to write the error at each iteration,
 
93
C         if this is desired for monitoring convergence.  If unit
 
94
C         number is 0, no writing will occur.
 
95
C RWORK  :WORK     Real RWORK(LENW).
 
96
C         Real array used for workspace.  NL is the number of non-
 
97
C         zeros in the lower triangle of the matrix (including the
 
98
C         diagonal).  NU is the number of non-zeros in the upper
 
99
C         triangle of the matrix (including the diagonal).
 
100
C LENW   :IN       Integer.
 
101
C         Length of the real workspace, RWORK.  LENW >= NL+NU+8*N.
 
102
C IWORK  :WORK     Integer IWORK(LENIW).
 
103
C         Integer array used for workspace.  NL is the number of non-
 
104
C         zeros in the lower triangle of the matrix (including the
 
105
C         diagonal).  NU is the number of non-zeros in the upper
 
106
C         triangle of the matrix (including the diagonal).
 
107
C         Upon return the following locations of IWORK hold information
 
108
C         which may be of use to the user:
 
109
C         IWORK(9)  Amount of Integer workspace actually used.
 
110
C         IWORK(10) Amount of Real workspace actually used.
 
111
C LENIW  :IN       Integer.
 
112
C         Length of the integer workspace, IWORK.
 
113
C         LENIW >= NL+NU+4*N+12.
 
114
C
 
115
C *Description:
 
116
C       This routine is simply a  driver for the SCGSN  routine.  It
 
117
C       calls the SSILUS routine to set  up the  preconditioning and
 
118
C       then  calls SCGSN with  the appropriate   MATVEC, MTTVEC and
 
119
C       MSOLVE, MTSOLV routines.
 
120
C
 
121
C       The Sparse Linear Algebra Package (SLAP) utilizes two matrix
 
122
C       data structures: 1) the  SLAP Triad  format or  2)  the SLAP
 
123
C       Column format.  The user can hand this routine either of the
 
124
C       of these data structures and SLAP  will figure out  which on
 
125
C       is being used and act accordingly.
 
126
C
 
127
C       =================== S L A P Triad format ===================
 
128
C
 
129
C       This routine requires that the  matrix A be   stored in  the
 
130
C       SLAP  Triad format.  In  this format only the non-zeros  are
 
131
C       stored.  They may appear in  *ANY* order.  The user supplies
 
132
C       three arrays of  length NELT, where  NELT is  the number  of
 
133
C       non-zeros in the matrix: (IA(NELT), JA(NELT), A(NELT)).  For
 
134
C       each non-zero the user puts the row and column index of that
 
135
C       matrix element  in the IA and  JA arrays.  The  value of the
 
136
C       non-zero   matrix  element is  placed  in  the corresponding
 
137
C       location of the A array.   This is  an  extremely  easy data
 
138
C       structure to generate.  On  the  other hand it   is  not too
 
139
C       efficient on vector computers for  the iterative solution of
 
140
C       linear systems.  Hence,   SLAP changes   this  input    data
 
141
C       structure to the SLAP Column format  for  the iteration (but
 
142
C       does not change it back).
 
143
C
 
144
C       Here is an example of the  SLAP Triad   storage format for a
 
145
C       5x5 Matrix.  Recall that the entries may appear in any order.
 
146
C
 
147
C           5x5 Matrix      SLAP Triad format for 5x5 matrix on left.
 
148
C                              1  2  3  4  5  6  7  8  9 10 11
 
149
C       |11 12  0  0 15|   A: 51 12 11 33 15 53 55 22 35 44 21
 
150
C       |21 22  0  0  0|  IA:  5  1  1  3  1  5  5  2  3  4  2
 
151
C       | 0  0 33  0 35|  JA:  1  2  1  3  5  3  5  2  5  4  1
 
152
C       | 0  0  0 44  0|
 
153
C       |51  0 53  0 55|
 
154
C
 
155
C       =================== S L A P Column format ==================
 
156
C
 
157
C       This routine  requires that  the matrix A  be stored in  the
 
158
C       SLAP Column format.  In this format the non-zeros are stored
 
159
C       counting down columns (except for  the diagonal entry, which
 
160
C       must appear first in each  "column")  and are stored  in the
 
161
C       real array A.  In other words, for each column in the matrix
 
162
C       put the diagonal entry in A.  Then put in the other non-zero
 
163
C       elements going down   the  column (except  the diagonal)  in
 
164
C       order.  The IA array holds the row  index for each non-zero.
 
165
C       The JA array holds the offsets into the IA, A arrays for the
 
166
C       beginning of   each    column.    That  is,    IA(JA(ICOL)),
 
167
C       A(JA(ICOL)) points to the beginning of the ICOL-th column in
 
168
C       IA and  A.  IA(JA(ICOL+1)-1),  A(JA(ICOL+1)-1) points to the
 
169
C       end  of   the ICOL-th  column.  Note   that  we  always have
 
170
C       JA(N+1) = NELT+1, where  N  is the number of columns in  the
 
171
C       matrix and  NELT   is the number of non-zeros in the matrix.
 
172
C
 
173
C       Here is an example of the  SLAP Column  storage format for a
 
174
C       5x5 Matrix (in the A and IA arrays '|'  denotes the end of a
 
175
C       column):
 
176
C
 
177
C           5x5 Matrix      SLAP Column format for 5x5 matrix on left.
 
178
C                              1  2  3    4  5    6  7    8    9 10 11
 
179
C       |11 12  0  0 15|   A: 11 21 51 | 22 12 | 33 53 | 44 | 55 15 35
 
180
C       |21 22  0  0  0|  IA:  1  2  5 |  2  1 |  3  5 |  4 |  5  1  3
 
181
C       | 0  0 33  0 35|  JA:  1  4  6    8  9   12
 
182
C       | 0  0  0 44  0|
 
183
C       |51  0 53  0 55|
 
184
C
 
185
C *Side Effects:
 
186
C       The SLAP Triad format (IA, JA,  A) is modified internally to
 
187
C       be the SLAP Column format.  See above.
 
188
C
 
189
C *Cautions:
 
190
C     This routine will attempt to write to the Fortran logical output
 
191
C     unit IUNIT, if IUNIT .ne. 0.  Thus, the user must make sure that
 
192
C     this logical unit is attached to a file or terminal before calling
 
193
C     this routine with a non-zero value for IUNIT.  This routine does
 
194
C     not check for the validity of a non-zero IUNIT unit number.
 
195
C
 
196
C***SEE ALSO  SCGS, SSDCGS
 
197
C***REFERENCES  1. P. Sonneveld, CGS, a fast Lanczos-type solver
 
198
C                  for nonsymmetric linear systems, Delft University
 
199
C                  of Technology Report 84-16, Department of Mathe-
 
200
C                  matics and Informatics, Delft, The Netherlands.
 
201
C               2. E. F. Kaasschieter, The solution of non-symmetric
 
202
C                  linear systems by biconjugate gradients or conjugate
 
203
C                  gradients squared,  Delft University of Technology
 
204
C                  Report 86-21, Department of Mathematics and Informa-
 
205
C                  tics, Delft, The Netherlands.
 
206
C***ROUTINES CALLED  SCGS, SCHKW, SS2Y, SSILUS, SSLUI, SSMV
 
207
C***REVISION HISTORY  (YYMMDD)
 
208
C   871119  DATE WRITTEN
 
209
C   881213  Previous REVISION DATE
 
210
C   890915  Made changes requested at July 1989 CML Meeting.  (MKS)
 
211
C   890921  Removed TeX from comments.  (FNF)
 
212
C   890922  Numerous changes to prologue to make closer to SLATEC
 
213
C           standard.  (FNF)
 
214
C   890929  Numerous changes to reduce SP/DP differences.  (FNF)
 
215
C   910411  Prologue converted to Version 4.0 format.  (BAB)
 
216
C   920511  Added complete declaration section.  (WRB)
 
217
C   920929  Corrected format of references.  (FNF)
 
218
C   921113  Corrected C***CATEGORY line.  (FNF)
 
219
C***END PROLOGUE  SSLUCS
 
220
C     .. Parameters ..
 
221
      INTEGER LOCRB, LOCIB
 
222
      PARAMETER (LOCRB=1, LOCIB=11)
 
223
C     .. Scalar Arguments ..
 
224
      REAL ERR, TOL
 
225
      INTEGER IERR, ISYM, ITER, ITMAX, ITOL, IUNIT, LENIW, LENW, N, NELT
 
226
C     .. Array Arguments ..
 
227
      REAL A(NELT), B(N), RWORK(LENW), X(N)
 
228
      INTEGER IA(NELT), IWORK(LENIW), JA(NELT)
 
229
C     .. Local Scalars ..
 
230
      INTEGER ICOL, J, JBGN, JEND, LOCDIN, LOCIL, LOCIU, LOCIW, LOCJL,
 
231
     +        LOCJU, LOCL, LOCNC, LOCNR, LOCP, LOCQ, LOCR, LOCR0, LOCU,
 
232
     +        LOCUU, LOCV1, LOCV2, LOCW, NL, NU
 
233
C     .. External Subroutines ..
 
234
      EXTERNAL SCGS, SCHKW, SS2Y, SSILUS, SSLUI, SSMV
 
235
C***FIRST EXECUTABLE STATEMENT  SSLUCS
 
236
C
 
237
      IERR = 0
 
238
      IF( N.LT.1 .OR. NELT.LT.1 ) THEN
 
239
         IERR = 3
 
240
         RETURN
 
241
      ENDIF
 
242
C
 
243
C         Change the SLAP input matrix IA, JA, A to SLAP-Column format.
 
244
      CALL SS2Y( N, NELT, IA, JA, A, ISYM )
 
245
C
 
246
C         Count number of Non-Zero elements preconditioner ILU matrix.
 
247
C         Then set up the work arrays.
 
248
      NL = 0
 
249
      NU = 0
 
250
      DO 20 ICOL = 1, N
 
251
C         Don't count diagonal.
 
252
         JBGN = JA(ICOL)+1
 
253
         JEND = JA(ICOL+1)-1
 
254
         IF( JBGN.LE.JEND ) THEN
 
255
CVD$ NOVECTOR
 
256
            DO 10 J = JBGN, JEND
 
257
               IF( IA(J).GT.ICOL ) THEN
 
258
                  NL = NL + 1
 
259
                  IF( ISYM.NE.0 ) NU = NU + 1
 
260
               ELSE
 
261
                  NU = NU + 1
 
262
               ENDIF
 
263
 10         CONTINUE
 
264
         ENDIF
 
265
 20   CONTINUE
 
266
C
 
267
      LOCIL = LOCIB
 
268
      LOCJL = LOCIL + N+1
 
269
      LOCIU = LOCJL + NL
 
270
      LOCJU = LOCIU + NU
 
271
      LOCNR = LOCJU + N+1
 
272
      LOCNC = LOCNR + N
 
273
      LOCIW = LOCNC + N
 
274
C
 
275
      LOCL   = LOCRB
 
276
      LOCDIN = LOCL + NL
 
277
      LOCUU  = LOCDIN + N
 
278
      LOCR   = LOCUU + NU
 
279
      LOCR0  = LOCR + N
 
280
      LOCP   = LOCR0 + N
 
281
      LOCQ   = LOCP + N
 
282
      LOCU   = LOCQ + N
 
283
      LOCV1  = LOCU + N
 
284
      LOCV2  = LOCV1 + N
 
285
      LOCW   = LOCV2 + N
 
286
C
 
287
C         Check the workspace allocations.
 
288
      CALL SCHKW( 'SSLUCS', LOCIW, LENIW, LOCW, LENW, IERR, ITER, ERR )
 
289
      IF( IERR.NE.0 ) RETURN
 
290
C
 
291
      IWORK(1) = LOCIL
 
292
      IWORK(2) = LOCJL
 
293
      IWORK(3) = LOCIU
 
294
      IWORK(4) = LOCJU
 
295
      IWORK(5) = LOCL
 
296
      IWORK(6) = LOCDIN
 
297
      IWORK(7) = LOCUU
 
298
      IWORK(9) = LOCIW
 
299
      IWORK(10) = LOCW
 
300
C
 
301
C         Compute the Incomplete LU decomposition.
 
302
      CALL SSILUS( N, NELT, IA, JA, A, ISYM, NL, IWORK(LOCIL),
 
303
     $     IWORK(LOCJL), RWORK(LOCL), RWORK(LOCDIN), NU, IWORK(LOCIU),
 
304
     $     IWORK(LOCJU), RWORK(LOCUU), IWORK(LOCNR), IWORK(LOCNC) )
 
305
C
 
306
C         Perform the incomplete LU preconditioned
 
307
C         BiConjugate Gradient Squared algorithm.
 
308
      CALL SCGS(N, B, X, NELT, IA, JA, A, ISYM, SSMV,
 
309
     $     SSLUI, ITOL, TOL, ITMAX, ITER, ERR, IERR, IUNIT,
 
310
     $     RWORK(LOCR), RWORK(LOCR0), RWORK(LOCP),
 
311
     $     RWORK(LOCQ), RWORK(LOCU), RWORK(LOCV1),
 
312
     $     RWORK(LOCV2), RWORK, IWORK )
 
313
      RETURN
 
314
C------------- LAST LINE OF SSLUCS FOLLOWS ----------------------------
 
315
      END