New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
solsor.F90 in branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/SOL – NEMO

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/SOL/solsor.F90 @ 2636

Last change on this file since 2636 was 2636, checked in by gm, 13 years ago

dynamic mem: #785 ; move ctl_stop & warn in lib_mpp to avoid a circular dependency + ctl_stop improvment

  • Property svn:keywords set to Id
File size: 7.9 KB
Line 
1MODULE solsor
2   !!======================================================================
3   !!                     ***  MODULE  solsor  ***
4   !! Ocean solver :  Successive Over-Relaxation solver
5   !!=====================================================================
6   !! History :  OPA  ! 1990-10  (G. Madec)  Original code
7   !!            7.1  ! 1993-04  (G. Madec)  time filter
8   !!                 ! 1996-05  (G. Madec)  merge sor and pcg formulations
9   !!                 ! 1996-11  (A. Weaver)  correction to preconditioning
10   !!   NEMO     1.0  ! 2003-04  (C. Deltel, G. Madec)  Red-Black SOR in free form
11   !!            2.0  ! 2005-09  (R. Benshila, G. Madec)  MPI optimization
12   !!----------------------------------------------------------------------
13
14   !!----------------------------------------------------------------------
15   !!   sol_sor     : Red-Black Successive Over-Relaxation solver
16   !!----------------------------------------------------------------------
17   USE oce             ! ocean dynamics and tracers variables
18   USE dom_oce         ! ocean space and time domain variables
19   USE zdf_oce         ! ocean vertical physics variables
20   USE sol_oce         ! solver variables
21   USE in_out_manager  ! I/O manager
22   USE lib_mpp         ! distributed memory computing
23   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
24   USE lib_fortran
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   sol_sor    !
30
31   !!----------------------------------------------------------------------
32   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
33   !! $Id$
34   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
35   !!----------------------------------------------------------------------
36CONTAINS
37     
38   SUBROUTINE sol_sor( kindic )
39      !!----------------------------------------------------------------------
40      !!                  ***  ROUTINE sol_sor  ***
41      !!                 
42      !! ** Purpose :   Solve the ellipic equation for the transport
43      !!      divergence system  using a red-black successive-over-
44      !!      relaxation method.
45      !!       This routine provides a MPI optimization to the existing solsor
46      !!     by reducing the number of call to lbc.
47      !!
48      !! ** Method  :   Successive-over-relaxation method using the red-black
49      !!      technique. The former technique used was not compatible with
50      !!      the north-fold boundary condition used in orca configurations.
51      !!      Compared to the classical sol_sor, this routine provides a
52      !!      mpp optimization by reducing the number of calls to lnc_lnk
53      !!      The solution is computed on a larger area and the boudary
54      !!      conditions only when the inside domain is reached.
55      !!
56      !! References :   Madec et al. 1988, Ocean Modelling, issue 78, 1-6.
57      !!                Beare and Stevens 1997 Ann. Geophysicae 15, 1369-1377
58      !!----------------------------------------------------------------------
59      USE wrk_nemo, ONLY:   wrk_in_use, wrk_not_released
60      USE wrk_nemo, ONLY:   ztab => wrk_2d_1    ! 2D workspace
61      !!
62      INTEGER, INTENT(inout) ::   kindic   ! solver indicator, < 0 if the convergence is not reached:
63      !                                    ! the model is stopped in step (set to zero before the call of solsor)
64      !!
65      INTEGER  ::   ji, jj, jn       ! dummy loop indices
66      INTEGER  ::   ishift, icount, ijmppodd, ijmppeven, ijpr2d   ! local integers
67      REAL(wp) ::   ztmp, zres, zres2                             ! local scalars
68      !!----------------------------------------------------------------------
69     
70      IF( wrk_in_use(2, 1) )THEN
71         CALL ctl_stop('sol_sor: requested workspace array is unavailable')   ;   RETURN
72      ENDIF
73
74      ijmppeven = MOD( nimpp+njmpp+jpr2di+jpr2dj   , 2 )
75      ijmppodd  = MOD( nimpp+njmpp+jpr2di+jpr2dj+1 , 2 )
76      ijpr2d    = MAX( jpr2di , jpr2dj )
77      icount = 0
78      !                                                       ! ==============
79      DO jn = 1, nn_nmax                                      ! Iterative loop
80         !                                                    ! ==============
81
82         IF( MOD(icount,ijpr2d+1) == 0 )   CALL lbc_lnk_e( gcx, c_solver_pt, 1. )   ! lateral boundary conditions
83       
84         ! Residus
85         ! -------
86
87         ! Guess black update
88         DO jj = 2-jpr2dj, nlcj-1+jpr2dj
89            ishift = MOD( jj-ijmppodd-jpr2dj, 2 )
90            DO ji = 2-jpr2di+ishift, nlci-1+jpr2di, 2
91               ztmp =                  gcb(ji  ,jj  )   &
92                  &   - gcp(ji,jj,1) * gcx(ji  ,jj-1)   &
93                  &   - gcp(ji,jj,2) * gcx(ji-1,jj  )   &
94                  &   - gcp(ji,jj,3) * gcx(ji+1,jj  )   &
95                  &   - gcp(ji,jj,4) * gcx(ji  ,jj+1)
96               ! Estimate of the residual
97               zres = ztmp - gcx(ji,jj)
98               gcr(ji,jj) = zres * gcdmat(ji,jj) * zres
99               ! Guess update
100               gcx(ji,jj) = rn_sor * ztmp + (1-rn_sor) * gcx(ji,jj)
101            END DO
102         END DO
103         icount = icount + 1 
104 
105         IF( MOD(icount,ijpr2d+1) == 0 )   CALL lbc_lnk_e( gcx, c_solver_pt, 1. )   ! lateral boundary conditions
106
107         ! Guess red update
108         DO jj = 2-jpr2dj, nlcj-1+jpr2dj
109            ishift = MOD( jj-ijmppeven-jpr2dj, 2 )
110            DO ji = 2-jpr2di+ishift, nlci-1+jpr2di, 2
111               ztmp =                  gcb(ji  ,jj  )   &
112                  &   - gcp(ji,jj,1) * gcx(ji  ,jj-1)   &
113                  &   - gcp(ji,jj,2) * gcx(ji-1,jj  )   &
114                  &   - gcp(ji,jj,3) * gcx(ji+1,jj  )   &
115                  &   - gcp(ji,jj,4) * gcx(ji  ,jj+1) 
116               ! Estimate of the residual
117               zres = ztmp - gcx(ji,jj)
118               gcr(ji,jj) = zres * gcdmat(ji,jj) * zres
119               ! Guess update
120               gcx(ji,jj) = rn_sor * ztmp + (1-rn_sor) * gcx(ji,jj)
121            END DO
122         END DO
123         icount = icount + 1
124
125         ! test of convergence
126         IF ( jn > nn_nmin .AND. MOD( jn-nn_nmin, nn_nmod ) == 0 ) THEN
127
128            SELECT CASE ( nn_sol_arp )
129            CASE ( 0 )                 ! absolute precision (maximum value of the residual)
130               zres2 = MAXVAL( gcr(2:nlci-1,2:nlcj-1) )
131               IF( lk_mpp )   CALL mpp_max( zres2 )   ! max over the global domain
132               ! test of convergence
133               IF( zres2 < rn_resmax .OR. jn == nn_nmax ) THEN
134                  res = SQRT( zres2 )
135                  niter = jn
136                  ncut = 999
137               ENDIF
138            CASE ( 1 )                 ! relative precision
139               ztab = 0.
140               ztab(:,:) = gcr(2:nlci-1,2:nlcj-1)
141               rnorme = glob_sum( ztab)    ! sum over the global domain
142               ! test of convergence
143               IF( rnorme < epsr .OR. jn == nn_nmax ) THEN
144                  res = SQRT( rnorme )
145                  niter = jn
146                  ncut = 999
147               ENDIF
148            END SELECT
149         
150         !****
151         !     IF(lwp)WRITE(numsol,9300) jn, res, sqrt( epsr ) / eps
1529300     FORMAT('          niter :',i4,' res :',e20.10,' b :',e20.10)
153         !****
154         
155         ENDIF
156         ! indicator of non-convergence or explosion
157         IF( jn == nn_nmax .OR. SQRT(epsr)/eps > 1.e+20 ) kindic = -2
158         IF( ncut == 999 ) GOTO 999
159         
160         !                                                 ! =====================
161      END DO                                               ! END of iterative loop
162      !                                                    ! =====================
163     
164999   CONTINUE
165     
166      !  Output in gcx
167      !  -------------
168      CALL lbc_lnk_e( gcx, c_solver_pt, 1. )    ! boundary conditions
169      !
170      IF( wrk_not_released(2, 1) )   CALL ctl_stop('sol_sor: failed to release workspace array')
171      !
172   END SUBROUTINE sol_sor
173
174   !!=====================================================================
175END MODULE solsor
Note: See TracBrowser for help on using the repository browser.