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 @ 120

Last change on this file since 120 was 120, checked in by opalod, 20 years ago

CT : UPDATE070 : Optimisation of the Red-Black SOR algorithm convergence

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 7.0 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 , LODYC-IPSL  (2003)
27   !!----------------------------------------------------------------------
28
29CONTAINS
30     
31   SUBROUTINE sol_sor( kindic )
32      !!----------------------------------------------------------------------
33      !!                  ***  ROUTINE sol_sor  ***
34      !!                 
35      !! ** Purpose :   Solve the ellipic equation for the barotropic stream
36      !!      function system (lk_dynspg_rl=T) or the transport divergence
37      !!      system (lk_dynspg_fsc=T) using a red-black successive-over-
38      !!      relaxation method.
39      !!       In the former case, the barotropic stream function trend has a
40      !!     zero boundary condition along all coastlines (i.e. continent
41      !!     as well as islands) while in the latter the boundary condition
42      !!     specification is not required.
43      !!
44      !! ** Method  :   Successive-over-relaxation method using the red-black
45      !!      technique. The former technique used was not compatible with
46      !!      the north-fold boundary condition used in orca configurations.
47      !!
48      !! References :
49      !!      Madec et al. 1988, Ocean Modelling, issue 78, 1-6.
50      !!
51      !! History :
52      !!        !  90-10  (G. Madec)  Original code
53      !!        !  91-11  (G. Madec)
54      !!   7.1  !  93-04  (G. Madec)  time filter
55      !!        !  96-05  (G. Madec)  merge sor and pcg formulations
56      !!        !  96-11  (A. Weaver)  correction to preconditioning
57      !!   9.0  !  03-04  (C. Deltel, G. Madec)  Red-Black SOR in free form
58      !!----------------------------------------------------------------------
59      !! * Arguments
60      INTEGER, INTENT( inout ) ::   kindic   ! solver indicator, < 0 if the conver-
61      !                                      ! gence is not reached: the model is
62      !                                      ! stopped in step
63      !                                      ! set to zero before the call of solsor
64      !! * Local declarations
65      INTEGER  ::   ji, jj, jn               ! dummy loop indices
66      INTEGER  ::   ishift
67      REAL(wp) ::   ztmp, zres, zres2
68
69      INTEGER  ::   ijmppodd, ijmppeven
70      !!----------------------------------------------------------------------
71     
72      ijmppeven = MOD(nimpp+njmpp  ,2)
73      ijmppodd  = MOD(nimpp+njmpp+1,2)
74      !                                                       ! ==============
75      DO jn = 1, nmax                                         ! Iterative loop
76         !                                                    ! ==============
77
78         CALL lbc_lnk( gcx, c_solver_pt, 1. )   ! applied the lateral boundary conditions
79         
80         ! Residus
81         ! -------
82
83         ! Guess black update
84         DO jj = 2, jpjm1
85            ishift = MOD( jj-ijmppodd, 2 )
86            DO ji = 2+ishift, jpim1, 2
87               ztmp =                  gcb(ji  ,jj  )   &
88                  &   - gcp(ji,jj,1) * gcx(ji  ,jj-1)   &
89                  &   - gcp(ji,jj,2) * gcx(ji-1,jj  )   &
90                  &   - gcp(ji,jj,3) * gcx(ji+1,jj  )   &
91                  &   - gcp(ji,jj,4) * gcx(ji  ,jj+1)
92               ! Estimate of the residual
93               zres = ztmp - gcx(ji,jj)
94               gcr(ji,jj) = zres * gcdmat(ji,jj) * zres
95               ! Guess update
96               gcx(ji,jj) = sor * ztmp + (1-sor) * gcx(ji,jj)
97            END DO
98         END DO
99
100         CALL lbc_lnk( gcx, c_solver_pt, 1. )   ! applied the lateral boubary conditions
101
102         ! Guess red update
103         DO jj = 2, jpjm1
104            ishift = MOD( jj-ijmppeven, 2 )
105            DO ji = 2+ishift, jpim1, 2
106               ztmp =                  gcb(ji  ,jj  )   &
107                  &   - gcp(ji,jj,1) * gcx(ji  ,jj-1)   &
108                  &   - gcp(ji,jj,2) * gcx(ji-1,jj  )   &
109                  &   - gcp(ji,jj,3) * gcx(ji+1,jj  )   &
110                  &   - gcp(ji,jj,4) * gcx(ji  ,jj+1) 
111               ! Estimate of the residual
112               zres = ztmp - gcx(ji,jj)
113               gcr(ji,jj) = zres * gcdmat(ji,jj) * zres
114               ! Guess update
115               gcx(ji,jj) = sor * ztmp + (1-sor) * gcx(ji,jj)
116            END DO
117         END DO
118
119         ! test of convergence
120         IF ( jn > nmin .AND. MOD( jn-nmin, nmod ) == 0 ) then
121
122            SELECT CASE ( nsol_arp )
123            CASE ( 0 )                 ! absolute precision (maximum value of the residual)
124               zres2 = MAXVAL( gcr(2:jpim1,2:jpjm1) )
125               IF( lk_mpp )   CALL mpp_max( zres2 )   ! max over the global domain
126               ! test of convergence
127               IF( zres2 < resmax .OR. jn == nmax ) THEN
128                  res = SQRT( zres2 )
129                  niter = jn
130                  ncut = 999
131               ENDIF
132            CASE ( 1 )                 ! relative precision
133               rnorme = SUM( gcr(2:jpim1,2:jpjm1) )
134               IF( lk_mpp )   CALL mpp_sum( rnorme )   ! sum over the global domain
135               ! test of convergence
136               IF( rnorme < epsr .OR. jn == nmax ) THEN
137                  res = SQRT( rnorme )
138                  niter = jn
139                  ncut = 999
140               ENDIF
141            END SELECT
142         
143         !****
144         !     IF(lwp)WRITE(numsol,9300) jn, res, sqrt( epsr ) / eps
1459300     FORMAT('          niter :',i4,' res :',e20.10,' b :',e20.10)
146         !****
147         
148         ENDIF
149         ! indicator of non-convergence or explosion
150         IF( jn == nmax .OR. SQRT(epsr)/eps > 1.e+20 ) kindic = -2
151         IF( ncut == 999 ) GOTO 999
152         
153         !                                                 ! =====================
154      END DO                                               ! END of iterative loop
155      !                                                    ! =====================
156     
157999   CONTINUE
158     
159     
160      !  Output in gcx
161      !  -------------
162
163      CALL lbc_lnk( gcx, c_solver_pt, 1. )    ! boundary conditions
164
165     
166   END SUBROUTINE sol_sor
167
168   !!=====================================================================
169END MODULE solsor
Note: See TracBrowser for help on using the repository browser.