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 trunk/NEMO/OPA_SRC/SOL – NEMO

source: trunk/NEMO/OPA_SRC/SOL/solsor.F90 @ 1566

Last change on this file since 1566 was 1528, checked in by rblod, 15 years ago

Suppress rigid-lid option, see ticket #486

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