/[MITgcm]/MITgcm_contrib/torge/itd/code/seaice_fgmres.F
ViewVC logotype

Contents of /MITgcm_contrib/torge/itd/code/seaice_fgmres.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.4 - (show annotations) (download)
Wed Mar 27 18:59:52 2013 UTC (12 years, 4 months ago) by torge
Branch: MAIN
CVS Tags: HEAD
Changes since 1.3: +386 -272 lines
updating my MITgcm_contrib directory to include latest changes on main branch;
settings are to run a 1D test szenario with ITD code and 7 categories

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_fgmres.F,v 1.16 2013/02/13 09:14:58 mlosch Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 C-- File seaice_fgmres.F: seaice fgmres dynamical (linear) solver S/R:
7 C-- Contents
8 C-- o SEAICE_FGMRES_DRIVER
9 C-- o SEAICE_MAP2VEC
10 C-- o SEAICE_MAP_RS2VEC
11 C-- o SEAICE_FGMRES
12 C-- o SEAICE_SCALPROD
13
14 CBOP
15 C !ROUTINE: SEAICE_FGMRES_DRIVER
16 C !INTERFACE:
17
18 SUBROUTINE SEAICE_FGMRES_DRIVER(
19 I uIceRes, vIceRes,
20 U duIce, dvIce,
21 U iCode,
22 I FGMRESeps, iOutFGMRES,
23 I newtonIter,
24 U krylovIter,
25 I myTime, myIter, myThid )
26
27 C !DESCRIPTION: \bv
28 C *==========================================================*
29 C | SUBROUTINE SEAICE_FGMRES_DRIVER
30 C | o driver routine for fgmres
31 C | o does the conversion between 2D fields and 1D vector
32 C | back and forth
33 C *==========================================================*
34 C | written by Martin Losch, Oct 2012
35 C *==========================================================*
36 C \ev
37
38 C !USES:
39 IMPLICIT NONE
40
41 C === Global variables ===
42 #include "SIZE.h"
43 #include "EEPARAMS.h"
44 #include "SEAICE_SIZE.h"
45 #include "SEAICE_PARAMS.h"
46
47 C !INPUT/OUTPUT PARAMETERS:
48 C === Routine arguments ===
49 C myTime :: Simulation time
50 C myIter :: Simulation timestep number
51 C myThid :: my Thread Id. number
52 C newtonIter :: current iterate of Newton iteration (for diagnostics)
53 C krylovIter :: current iterate of Newton iteration (updated)
54 C iCode :: FGMRES parameter to determine next step
55 C iOutFGMRES :: control output of fgmres
56 _RL myTime
57 INTEGER myIter
58 INTEGER myThid
59 INTEGER newtonIter
60 INTEGER krylovIter
61 INTEGER iOutFGMRES
62 INTEGER iCode
63 C FGMRESeps :: tolerance for FGMRES
64 _RL FGMRESeps
65 C du/vIce :: solution vector
66 _RL duIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
67 _RL dvIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
68 C u/vIceRes :: residual F(u)
69 _RL uIceRes(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
70 _RL vIceRes(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
71
72 #if ( defined (SEAICE_CGRID) && \
73 defined (SEAICE_ALLOW_JFNK) && \
74 defined (SEAICE_ALLOW_DYNAMICS) )
75 C Local variables:
76 C k :: loop indices
77 INTEGER k, bi, bj
78 C FGMRES parameters
79 C nVec :: size of the input vector(s)
80 C im :: size of Krylov space
81 C ifgmres :: interation counter
82 INTEGER nVec
83 PARAMETER ( nVec = 2*sNx*sNy )
84 INTEGER im
85 PARAMETER ( im = 50 )
86 INTEGER ifgmres
87 C work arrays
88 _RL rhs(nVec,nSx,nSy), sol(nVec,nSx,nSy)
89 _RL vv(nVec,im+1,nSx,nSy), w(nVec,im,nSx,nSy)
90 _RL wk1(nVec,nSx,nSy), wk2(nVec,nSx,nSy)
91 C need to store some of the fgmres parameters and fields so that
92 C they are not forgotten between Krylov iterations
93 COMMON /FGMRES_I/ ifgmres
94 COMMON /FGMRES_RL/ sol, rhs, vv, w
95 CEOP
96
97 IF ( iCode .EQ. 0 ) THEN
98 C The first guess is zero because it is a correction, but this
99 C is implemented by setting du/vIce=0 outside of this routine;
100 C this make it possible to restart FGMRES with a nonzero sol
101 CALL SEAICE_MAP2VEC(nVec,duIce,dvIce,sol,.TRUE.,myThid)
102 C wk2 needs to be reset for iCode = 0, because it may contain
103 C remains of the previous Krylov iteration
104 DO bj=myByLo(myThid),myByHi(myThid)
105 DO bi=myBxLo(myThid),myBxHi(myThid)
106 DO k=1,nVec
107 wk2(k,bi,bj) = 0. _d 0
108 ENDDO
109 ENDDO
110 ENDDO
111 ELSEIF ( iCode .EQ. 3 ) THEN
112 CALL SEAICE_MAP2VEC(nVec,uIceRes,vIceRes,rhs,.TRUE.,myThid)
113 C change sign of rhs because we are solving J*u = -F
114 C wk2 needs to be initialised for iCode = 3, because it may contain
115 C garbage
116 DO bj=myByLo(myThid),myByHi(myThid)
117 DO bi=myBxLo(myThid),myBxHi(myThid)
118 DO k=1,nVec
119 rhs(k,bi,bj) = -rhs(k,bi,bj)
120 wk2(k,bi,bj) = 0. _d 0
121 ENDDO
122 ENDDO
123 ENDDO
124 ELSE
125 C map preconditioner results or Jacobian times vector,
126 C stored in du/vIce to wk2
127 CALL SEAICE_MAP2VEC(nVec,duIce,dvIce,wk2,.TRUE.,myThid)
128 ENDIF
129 C
130 CALL SEAICE_FGMRES (nVec,im,rhs,sol,ifgmres,krylovIter,
131 U vv,w,wk1,wk2,
132 I FGMRESeps,SEAICEkrylovIterMax,iOutFGMRES,
133 U iCode,
134 I myThid)
135 C
136 IF ( iCode .EQ. 0 ) THEN
137 C map sol(ution) vector to du/vIce
138 CALL SEAICE_MAP2VEC(nVec,duIce,dvIce,sol,.FALSE.,myThid)
139 ELSE
140 C map work vector to du/vIce to either compute a preconditioner
141 C solution (wk1=rhs) or a Jacobian times wk1
142 CALL SEAICE_MAP2VEC(nVec,duIce,dvIce,wk1,.FALSE.,myThid)
143 ENDIF
144
145 C Fill overlaps in updated fields
146 CALL EXCH_UV_XY_RL( duIce, dvIce,.TRUE.,myThid)
147
148 RETURN
149 END
150
151 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
152 CBOP
153 C !ROUTINE: SEAICE_MAP2VEC
154 C !INTERFACE:
155
156 SUBROUTINE SEAICE_MAP2VEC(
157 I n,
158 O xfld2d, yfld2d,
159 U vector,
160 I map2vec, myThid )
161
162 C !DESCRIPTION: \bv
163 C *==========================================================*
164 C | SUBROUTINE SEAICE_MAP2VEC
165 C | o maps 2 2D-fields to vector and back
166 C *==========================================================*
167 C | written by Martin Losch, Oct 2012
168 C *==========================================================*
169 C \ev
170
171 C !USES:
172 IMPLICIT NONE
173
174 C === Global variables ===
175 #include "SIZE.h"
176 #include "EEPARAMS.h"
177 C === Routine arguments ===
178 INTEGER n
179 LOGICAL map2vec
180 INTEGER myThid
181 _RL xfld2d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
182 _RL yfld2d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
183 _RL vector (n,nSx,nSy)
184 C === local variables ===
185 INTEGER I, J, bi, bj
186 INTEGER ii, jj, m
187 CEOP
188
189 m = n/2
190 DO bj=myByLo(myThid),myByHi(myThid)
191 DO bi=myBxLo(myThid),myBxHi(myThid)
192 #ifdef SEAICE_JFNK_MAP_REORDER
193 ii = 0
194 IF ( map2vec ) THEN
195 DO J=1,sNy
196 jj = 2*sNx*(J-1)
197 DO I=1,sNx
198 ii = jj + 2*I
199 vector(ii-1,bi,bj) = xfld2d(I,J,bi,bj)
200 vector(ii, bi,bj) = yfld2d(I,J,bi,bj)
201 ENDDO
202 ENDDO
203 ELSE
204 DO J=1,sNy
205 jj = 2*sNx*(J-1)
206 DO I=1,sNx
207 ii = jj + 2*I
208 xfld2d(I,J,bi,bj) = vector(ii-1,bi,bj)
209 yfld2d(I,J,bi,bj) = vector(ii, bi,bj)
210 ENDDO
211 ENDDO
212 ENDIF
213 #else
214 IF ( map2vec ) THEN
215 DO J=1,sNy
216 jj = sNx*(J-1)
217 DO I=1,sNx
218 ii = jj + I
219 vector(ii, bi,bj) = xfld2d(I,J,bi,bj)
220 vector(ii+m,bi,bj) = yfld2d(I,J,bi,bj)
221 ENDDO
222 ENDDO
223 ELSE
224 DO J=1,sNy
225 jj = sNx*(J-1)
226 DO I=1,sNx
227 ii = jj + I
228 xfld2d(I,J,bi,bj) = vector(ii, bi,bj)
229 yfld2d(I,J,bi,bj) = vector(ii+m,bi,bj)
230 ENDDO
231 ENDDO
232 ENDIF
233 #endif /* SEAICE_JFNK_MAP_REORDER */
234 C bi,bj-loops
235 ENDDO
236 ENDDO
237
238 RETURN
239 END
240
241 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
242 CBOP
243 C !ROUTINE: SEAICE_MAP_RS2VEC
244 C !INTERFACE:
245
246 SUBROUTINE SEAICE_MAP_RS2VEC(
247 I n,
248 O xfld2d, yfld2d,
249 U vector,
250 I map2vec, myThid )
251
252 C !DESCRIPTION: \bv
253 C *==========================================================*
254 C | SUBROUTINE SEAICE_MAP_RS2VEC
255 C | o maps 2 2D-RS-fields to vector and back
256 C *==========================================================*
257 C | written by Martin Losch, Oct 2012
258 C *==========================================================*
259 C \ev
260
261 C !USES:
262 IMPLICIT NONE
263
264 C === Global variables ===
265 #include "SIZE.h"
266 #include "EEPARAMS.h"
267 C === Routine arguments ===
268 INTEGER n
269 LOGICAL map2vec
270 INTEGER myThid
271 _RS xfld2d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
272 _RS yfld2d (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
273 _RL vector (n,nSx,nSy)
274 C === local variables ===
275 INTEGER I, J, bi, bj
276 INTEGER ii, jj, m
277 CEOP
278
279 m = n/2
280 DO bj=myByLo(myThid),myByHi(myThid)
281 DO bi=myBxLo(myThid),myBxHi(myThid)
282 #ifdef SEAICE_JFNK_MAP_REORDER
283 ii = 0
284 IF ( map2vec ) THEN
285 DO J=1,sNy
286 jj = 2*sNx*(J-1)
287 DO I=1,sNx
288 ii = jj + 2*I
289 vector(ii-1,bi,bj) = xfld2d(I,J,bi,bj)
290 vector(ii, bi,bj) = yfld2d(I,J,bi,bj)
291 ENDDO
292 ENDDO
293 ELSE
294 DO J=1,sNy
295 jj = 2*sNx*(J-1)
296 DO I=1,sNx
297 ii = jj + 2*I
298 xfld2d(I,J,bi,bj) = vector(ii-1,bi,bj)
299 yfld2d(I,J,bi,bj) = vector(ii, bi,bj)
300 ENDDO
301 ENDDO
302 ENDIF
303 #else
304 IF ( map2vec ) THEN
305 DO J=1,sNy
306 jj = sNx*(J-1)
307 DO I=1,sNx
308 ii = jj + I
309 vector(ii, bi,bj) = xfld2d(I,J,bi,bj)
310 vector(ii+m,bi,bj) = yfld2d(I,J,bi,bj)
311 ENDDO
312 ENDDO
313 ELSE
314 DO J=1,sNy
315 jj = sNx*(J-1)
316 DO I=1,sNx
317 ii = jj + I
318 xfld2d(I,J,bi,bj) = vector(ii, bi,bj)
319 yfld2d(I,J,bi,bj) = vector(ii+m,bi,bj)
320 ENDDO
321 ENDDO
322 ENDIF
323 #endif /* SEAICE_JFNK_MAP_REORDER */
324 C bi,bj-loops
325 ENDDO
326 ENDDO
327
328 RETURN
329 END
330
331 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
332 CBOP
333 C !ROUTINE: SEAICE_FGMRES
334 C !INTERFACE:
335 SUBROUTINE SEAICE_FGMRES (
336 I n,im,rhs,
337 U sol,i,its,vv,w,wk1,wk2,
338 I eps,maxits,iout,
339 U icode,
340 I myThid )
341
342 C-----------------------------------------------------------------------
343 C mlosch Oct 2012: modified the routine further to be compliant with
344 C MITgcm standards:
345 C f90 -> F
346 C !-comment -> C-comment
347 C add its to list of arguments
348 C double precision -> _RL
349 C implicit none
350 C
351 C jfl Dec 1st 2006. We modified the routine so that it is double precison.
352 C Here are the modifications:
353 C 1) implicit real (a-h,o-z) becomes implicit real*8 (a-h,o-z)
354 C 2) real bocomes real*8
355 C 3) subroutine scopy.f has been changed for dcopy.f
356 C 4) subroutine saxpy.f has been changed for daxpy.f
357 C 5) function sdot.f has been changed for ddot.f
358 C 6) 1e-08 becomes 1d-08
359 C
360 C Be careful with the dcopy, daxpy and ddot code...there is a slight
361 C difference with the single precision versions (scopy, saxpy and sdot).
362 C In the single precision versions, the array are declared sightly differently.
363 C It is written for single precision:
364 C
365 C modified 12/3/93, array(1) declarations changed to array(*)
366 C-----------------------------------------------------------------------
367
368 implicit none
369 C === Global variables ===
370 #include "SIZE.h"
371 #include "EEPARAMS.h"
372 CML implicit double precision (a-h,o-z) !jfl modification
373 integer myThid
374 integer n, im, its, maxits, iout, icode
375 _RL rhs(n,nSx,nSy), sol(n,nSx,nSy)
376 _RL vv(n,im+1,nSx,nSy), w(n,im,nSx,nSy)
377 _RL wk1(n,nSx,nSy), wk2(n,nSx,nSy), eps
378 C-----------------------------------------------------------------------
379 C flexible GMRES routine. This is a version of GMRES which allows a
380 C a variable preconditioner. Implemented with a reverse communication
381 C protocole for flexibility -
382 C DISTRIBUTED VERSION (USES DISTDOT FOR DDOT)
383 C explicit (exact) residual norms for restarts
384 C written by Y. Saad, modified by A. Malevsky, version February 1, 1995
385 C-----------------------------------------------------------------------
386 C This Is A Reverse Communication Implementation.
387 C-------------------------------------------------
388 C USAGE: (see also comments for icode below). FGMRES
389 C should be put in a loop and the loop should be active for as
390 C long as icode is not equal to 0. On return fgmres will
391 C 1) either be requesting the new preconditioned vector applied
392 C to wk1 in case icode.eq.1 (result should be put in wk2)
393 C 2) or be requesting the product of A applied to the vector wk1
394 C in case icode.eq.2 (result should be put in wk2)
395 C 3) or be terminated in case icode .eq. 0.
396 C on entry always set icode = 0. So icode should be set back to zero
397 C upon convergence.
398 C-----------------------------------------------------------------------
399 C Here is a typical way of running fgmres:
400 C
401 C icode = 0
402 C 1 continue
403 C call fgmres (n,im,rhs,sol,i,vv,w,wk1,wk2,eps,maxits,iout,
404 C & icode,its,mythid)
405 C
406 C if (icode .eq. 1) then
407 C call precon(n, wk1, wk2) <--- user variable preconditioning
408 C goto 1
409 C else if (icode .ge. 2) then
410 C call matvec (n,wk1, wk2) <--- user matrix vector product.
411 C goto 1
412 C else
413 C ----- done ----
414 C .........
415 C-----------------------------------------------------------------------
416 C list of parameters
417 C-------------------
418 C
419 C n == integer. the dimension of the problem
420 C im == size of Krylov subspace: should not exceed 50 in this
421 C version (can be reset in code. looking at comment below)
422 C rhs == vector of length n containing the right hand side
423 C sol == initial guess on input, approximate solution on output
424 C vv == work space of size n x (im+1)
425 C w == work space of length n x im
426 C wk1,
427 C wk2, == two work vectors of length n each used for the reverse
428 C communication protocole. When on return (icode .ne. 1)
429 C the user should call fgmres again with wk2 = precon * wk1
430 C and icode untouched. When icode.eq.1 then it means that
431 C convergence has taken place.
432 C
433 C eps == tolerance for stopping criterion. process is stopped
434 C as soon as ( ||.|| is the euclidean norm):
435 C || current residual||/||initial residual|| <= eps
436 C
437 C maxits== maximum number of iterations allowed
438 C
439 C i == internal iteration counter, updated in this routine
440 C its == current (Krylov) iteration counter, updated in this routine
441 C
442 C iout == output unit number number for printing intermediate results
443 C if (iout .le. 0) no statistics are printed.
444 C
445 C icode = integer. indicator for the reverse communication protocole.
446 C ON ENTRY : icode should be set to icode = 0.
447 C ON RETURN:
448 C * icode .eq. 1 value means that fgmres has not finished
449 C and that it is requesting a preconditioned vector before
450 C continuing. The user must compute M**(-1) wk1, where M is
451 C the preconditioing matrix (may vary at each call) and wk1 is
452 C the vector as provided by fgmres upun return, and put the
453 C result in wk2. Then fgmres must be called again without
454 C changing any other argument.
455 C * icode .eq. 2 value means that fgmres has not finished
456 C and that it is requesting a matrix vector product before
457 C continuing. The user must compute A * wk1, where A is the
458 C coefficient matrix and wk1 is the vector provided by
459 C upon return. The result of the operation is to be put in
460 C the vector wk2. Then fgmres must be called again without
461 C changing any other argument.
462 C * icode .eq. 0 means that fgmres has finished and sol contains
463 C the approximate solution.
464 C comment: typically fgmres must be implemented in a loop
465 C with fgmres being called as long icode is returned with
466 C a value .ne. 0.
467 C-----------------------------------------------------------------------
468 C local variables -- !jfl modif
469 integer imax
470 parameter ( imax = 50 )
471 _RL hh(4*imax+1,4*imax),c(4*imax),s(4*imax)
472 _RL rs(4*imax+1),t,ro
473 C-------------------------------------------------------------
474 C arnoldi size should not exceed 50 in this version..
475 C-------------------------------------------------------------
476 integer i, i1, ii, j, jj, k, k1!, n1
477 integer bi, bj
478 _RL r0, gam, epsmac, eps1
479 CHARACTER*(MAX_LEN_MBUF) msgBuf
480
481 CEOP
482 CML save
483 C local common block to replace the save statement
484 COMMON /SEAICE_FMRES_LOC_I/ i1
485 COMMON /SEAICE_FMRES_LOC_RL/
486 & hh, c, s, rs, t, ro, r0, gam, epsmac, eps1
487 data epsmac/1.d-16/
488 C
489 C computed goto
490 C
491 if ( im .gt. imax ) stop 'size of krylov space > 50'
492 goto (100,200,300,11) icode +1
493 100 continue
494 CML n1 = n + 1
495 its = 0
496 C-------------------------------------------------------------
497 C ** outer loop starts here..
498 C--------------compute initial residual vector --------------
499 C 10 continue
500 CML call dcopy (n, sol, 1, wk1, 1) !jfl modification
501 do bj=myByLo(myThid),myByHi(myThid)
502 do bi=myBxLo(myThid),myBxHi(myThid)
503 do j=1,n
504 wk1(j,bi,bj)=sol(j,bi,bj)
505 enddo
506 enddo
507 enddo
508 icode = 3
509 RETURN
510 11 continue
511 do bj=myByLo(myThid),myByHi(myThid)
512 do bi=myBxLo(myThid),myBxHi(myThid)
513 do j=1,n
514 vv(j,1,bi,bj) = rhs(j,bi,bj) - wk2(j,bi,bj)
515 enddo
516 enddo
517 enddo
518 20 continue
519 CML ro = ddot(n, vv, 1, vv,1) !jfl modification
520 call SEAICE_SCALPROD(n, im+1, 1, 1, vv, vv, ro, myThid)
521 ro = sqrt(ro)
522 if (ro .eq. 0.0 _d 0) goto 999
523 t = 1.0 _d 0/ ro
524 do bj=myByLo(myThid),myByHi(myThid)
525 do bi=myBxLo(myThid),myBxHi(myThid)
526 do j=1, n
527 vv(j,1,bi,bj) = vv(j,1,bi,bj)*t
528 enddo
529 enddo
530 enddo
531 if (its .eq. 0) eps1=eps
532 C not sure what this is, r0 is never used again
533 if (its .eq. 0) r0 = ro
534 if (iout .gt. 0) then
535 _BEGIN_MASTER( myThid )
536 write(msgBuf, 199) its, ro
537 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
538 & SQUEEZE_RIGHT, myThid )
539 C print *,'chau',its, ro !write(iout, 199) its, ro
540 _END_MASTER( myThid )
541 endif
542 C
543 C initialize 1-st term of rhs of hessenberg system..
544 C
545 rs(1) = ro
546 i = 0
547 4 continue
548 i=i+1
549 its = its + 1
550 i1 = i + 1
551 do bj=myByLo(myThid),myByHi(myThid)
552 do bi=myBxLo(myThid),myBxHi(myThid)
553 do k=1, n
554 wk1(k,bi,bj) = vv(k,i,bi,bj)
555 enddo
556 enddo
557 enddo
558 C
559 C return
560 C
561 icode = 1
562 RETURN
563 200 continue
564 do bj=myByLo(myThid),myByHi(myThid)
565 do bi=myBxLo(myThid),myBxHi(myThid)
566 do k=1, n
567 w(k,i,bi,bj) = wk2(k,bi,bj)
568 enddo
569 enddo
570 enddo
571 C
572 C call matvec operation
573 C
574 CML call dcopy(n, wk2, 1, wk1, 1) !jfl modification
575 do bj=myByLo(myThid),myByHi(myThid)
576 do bi=myBxLo(myThid),myBxHi(myThid)
577 do k=1,n
578 wk1(k,bi,bj)=wk2(k,bi,bj)
579 enddo
580 enddo
581 enddo
582 C
583 C return
584 C
585 icode = 2
586 RETURN
587 300 continue
588 C
589 C first call to ope corresponds to intialization goto back to 11.
590 C
591 C if (icode .eq. 3) goto 11
592 CML call dcopy (n, wk2, 1, vv(1,i1), 1) !jfl modification
593 do bj=myByLo(myThid),myByHi(myThid)
594 do bi=myBxLo(myThid),myBxHi(myThid)
595 do k=1,n
596 vv(k,i1,bi,bj)=wk2(k,bi,bj)
597 enddo
598 enddo
599 enddo
600 C
601 C modified gram - schmidt...
602 C
603 do j=1, i
604 CML t = ddot(n, vv(1,j), 1, vv(1,i1), 1) !jfl modification
605 call SEAICE_SCALPROD(n, im+1, j, i1, vv, vv, t, myThid)
606 hh(j,i) = t
607 CML call daxpy(n, -t, vv(1,j), 1, vv(1,i1), 1) !jfl modification
608 CML enddo
609 CML do j=1, i
610 CML t = hh(j,i)
611 do bj=myByLo(myThid),myByHi(myThid)
612 do bi=myBxLo(myThid),myBxHi(myThid)
613 do k=1,n
614 vv(k,i1,bi,bj) = vv(k,i1,bi,bj) - t*vv(k,j,bi,bj)
615 enddo
616 enddo
617 enddo
618 enddo
619 CML t = sqrt(ddot(n, vv(1,i1), 1, vv(1,i1), 1)) !jfl modification
620 call SEAICE_SCALPROD(n, im+1, i1, i1, vv, vv, t, myThid)
621 t = sqrt(t)
622 hh(i1,i) = t
623 if (t .ne. 0.0 _d 0) then
624 t = 1.0 _d 0 / t
625 do bj=myByLo(myThid),myByHi(myThid)
626 do bi=myBxLo(myThid),myBxHi(myThid)
627 do k=1,n
628 vv(k,i1,bi,bj) = vv(k,i1,bi,bj)*t
629 enddo
630 enddo
631 enddo
632 endif
633 C
634 C done with modified gram schimd and arnoldi step.
635 C now update factorization of hh
636 C
637 if (i .ne. 1) then
638 C
639 C perfrom previous transformations on i-th column of h
640 C
641 do k=2,i
642 k1 = k-1
643 t = hh(k1,i)
644 hh(k1,i) = c(k1)*t + s(k1)*hh(k,i)
645 hh(k,i) = -s(k1)*t + c(k1)*hh(k,i)
646 enddo
647 endif
648 gam = sqrt(hh(i,i)**2 + hh(i1,i)**2)
649 if (gam .eq. 0.0 _d 0) gam = epsmac
650 C-----------#determine next plane rotation #-------------------
651 c(i) = hh(i,i)/gam
652 s(i) = hh(i1,i)/gam
653 C numerically more stable Givens rotation, but the results
654 C are not better
655 CML c(i)=1. _d 0
656 CML s(i)=0. _d 0
657 CML if ( abs(hh(i1,i)) .gt. 0.0 _d 0) then
658 CML if ( abs(hh(i1,i)) .gt. abs(hh(i,i)) ) then
659 CML gam = hh(i,i)/hh(i1,i)
660 CML s(i) = 1./sqrt(1.+gam*gam)
661 CML c(i) = s(i)*gam
662 CML else
663 CML gam = hh(i1,i)/hh(i,i)
664 CML c(i) = 1./sqrt(1.+gam*gam)
665 CML s(i) = c(i)*gam
666 CML endif
667 CML endif
668 rs(i1) = -s(i)*rs(i)
669 rs(i) = c(i)*rs(i)
670 C
671 C determine res. norm. and test for convergence
672 C
673 hh(i,i) = c(i)*hh(i,i) + s(i)*hh(i1,i)
674 ro = abs(rs(i1))
675 if (iout .gt. 0) then
676 _BEGIN_MASTER( myThid )
677 write(msgBuf, 199) its, ro
678 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
679 & SQUEEZE_RIGHT, myThid )
680 _END_MASTER( myThid )
681 endif
682 if (i .lt. im .and. (ro .gt. eps1)) goto 4
683 C
684 C now compute solution. first solve upper triangular system.
685 C
686 rs(i) = rs(i)/hh(i,i)
687 do ii=2,i
688 k=i-ii+1
689 k1 = k+1
690 t=rs(k)
691 do j=k1,i
692 t = t-hh(k,j)*rs(j)
693 enddo
694 rs(k) = t/hh(k,k)
695 enddo
696 C
697 C done with back substitution..
698 C now form linear combination to get solution
699 C
700 do j=1, i
701 t = rs(j)
702 CML call daxpy(n, t, w(1,j), 1, sol,1) !jfl modification
703 do bj=myByLo(myThid),myByHi(myThid)
704 do bi=myBxLo(myThid),myBxHi(myThid)
705 do k=1,n
706 sol(k,bi,bj) = sol(k,bi,bj) + t*w(k,j,bi,bj)
707 enddo
708 enddo
709 enddo
710 enddo
711 C
712 C test for return
713 C
714 if (ro .le. eps1 .or. its .ge. maxits) goto 999
715 C
716 C else compute residual vector and continue..
717 C
718 C goto 10
719
720 do j=1,i
721 jj = i1-j+1
722 rs(jj-1) = -s(jj-1)*rs(jj)
723 rs(jj) = c(jj-1)*rs(jj)
724 enddo
725 do j=1,i1
726 t = rs(j)
727 if (j .eq. 1) t = t-1.0 _d 0
728 CML call daxpy (n, t, vv(1,j), 1, vv, 1)
729 do bj=myByLo(myThid),myByHi(myThid)
730 do bi=myBxLo(myThid),myBxHi(myThid)
731 do k=1,n
732 vv(k,1,bi,bj) = vv(k,1,bi,bj) + t*vv(k,j,bi,bj)
733 enddo
734 enddo
735 enddo
736 enddo
737 C
738 C restart outer loop.
739 C
740 goto 20
741 999 icode = 0
742
743 199 format(' SEAICE_FGMRES: its =', i4, ' res. norm =', d26.16)
744 C
745 RETURN
746 C-----end-of-fgmres-----------------------------------------------------
747 C-----------------------------------------------------------------------
748 END
749
750 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
751 CBOP
752 C !ROUTINE: SEAICE_SCALPROD
753 C !INTERFACE:
754
755 subroutine SEAICE_SCALPROD(n,im,i1,i2,dx,dy,t,myThid)
756
757 C forms the dot product of two vectors.
758 C uses unrolled loops for increments equal to one.
759 C jack dongarra, linpack, 3/11/78.
760 C ML: code stolen from BLAS-ddot and adapted for parallel applications
761
762 implicit none
763 #include "SIZE.h"
764 #include "EEPARAMS.h"
765 #include "EESUPPORT.h"
766 #include "SEAICE_SIZE.h"
767 #include "SEAICE.h"
768 integer n, im, i1, i2
769 _RL dx(n,im,nSx,nSy),dy(n,im,nSx,nSy)
770 _RL t
771 integer myThid
772 C local arrays
773 _RL dtemp(nSx,nSy)
774 integer i,m,mp1,bi,bj
775 CEOP
776
777 m = mod(n,5)
778 mp1 = m + 1
779 t = 0. _d 0
780 c if( m .eq. 0 ) go to 40
781 do bj=myByLo(myThid),myByHi(myThid)
782 do bi=myBxLo(myThid),myBxHi(myThid)
783 dtemp(bi,bj) = 0. _d 0
784 if ( m .ne. 0 ) then
785 do i = 1,m
786 dtemp(bi,bj) = dtemp(bi,bj) + dx(i,i1,bi,bj)*dy(i,i2,bi,bj)
787 & * scalarProductMetric(i,1,bi,bj)
788 enddo
789 endif
790 if ( n .ge. 5 ) then
791 c if( n .lt. 5 ) go to 60
792 c40 mp1 = m + 1
793 do i = mp1,n,5
794 dtemp(bi,bj) = dtemp(bi,bj) +
795 & dx(i, i1,bi,bj)*dy(i, i2,bi,bj)
796 & * scalarProductMetric(i, 1, bi,bj) +
797 & dx(i + 1,i1,bi,bj)*dy(i + 1,i2,bi,bj)
798 & * scalarProductMetric(i + 1,1, bi,bj) +
799 & dx(i + 2,i1,bi,bj)*dy(i + 2,i2,bi,bj)
800 & * scalarProductMetric(i + 2,1, bi,bj) +
801 & dx(i + 3,i1,bi,bj)*dy(i + 3,i2,bi,bj)
802 & * scalarProductMetric(i + 3,1, bi,bj) +
803 & dx(i + 4,i1,bi,bj)*dy(i + 4,i2,bi,bj)
804 & * scalarProductMetric(i + 4,1, bi,bj)
805 enddo
806 c60 continue
807 endif
808 enddo
809 enddo
810 CALL GLOBAL_SUM_TILE_RL( dtemp,t,myThid )
811
812 #endif /* SEAICE_ALLOW_DYNAMICS and SEAICE_CGRID and SEAICE_ALLOW_JFNK */
813
814 RETURN
815 END

  ViewVC Help
Powered by ViewVC 1.1.22