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

Last change on this file since 2011 was 1601, checked in by ctlod, 15 years ago

Doctor naming of OPA namelist variables , see ticket: #526

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 7.5 KB
RevLine 
[3]1MODULE solsor
2   !!======================================================================
[86]3   !!                     ***  MODULE  solsor  ***
[3]4   !! Ocean solver :  Successive Over-Relaxation solver
5   !!=====================================================================
[1601]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   !!----------------------------------------------------------------------
[3]13
14   !!----------------------------------------------------------------------
[86]15   !!   sol_sor     : Red-Black Successive Over-Relaxation solver
[3]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
25   IMPLICIT NONE
26   PRIVATE
27
[1601]28   PUBLIC   sol_sor    !
[16]29
[3]30   !!----------------------------------------------------------------------
[1601]31   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
[1152]32   !! $Id$
[1601]33   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
[3]34   !!----------------------------------------------------------------------
35
36CONTAINS
37     
[16]38   SUBROUTINE sol_sor( kindic )
[3]39      !!----------------------------------------------------------------------
40      !!                  ***  ROUTINE sol_sor  ***
41      !!                 
[1528]42      !! ** Purpose :   Solve the ellipic equation for the transport
43      !!      divergence system  using a red-black successive-over-
[86]44      !!      relaxation method.
[784]45      !!       This routine provides a MPI optimization to the existing solsor
46      !!     by reducing the number of call to lbc.
47      !!
[3]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.
[784]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      !!
[1601]56      !! References :   Madec et al. 1988, Ocean Modelling, issue 78, 1-6.
57      !!                Beare and Stevens 1997 Ann. Geophysicae 15, 1369-1377
58      !!----------------------------------------------------------------------
59      INTEGER, INTENT(inout) ::   kindic   ! solver indicator, < 0 if the convergence is not reached:
60      !                                    ! the model is stopped in step (set to zero before the call of solsor)
[3]61      !!
62      INTEGER  ::   ji, jj, jn               ! dummy loop indices
[784]63      INTEGER  ::   ishift, icount
[1601]64      INTEGER  ::   ijmppodd, ijmppeven, ijpr2d
[86]65      REAL(wp) ::   ztmp, zres, zres2
[3]66      !!----------------------------------------------------------------------
67     
[1601]68      ijmppeven = MOD( nimpp+njmpp+jpr2di+jpr2dj   , 2 )
69      ijmppodd  = MOD( nimpp+njmpp+jpr2di+jpr2dj+1 , 2 )
70      ijpr2d    = MAX( jpr2di , jpr2dj )
[784]71      icount = 0
[16]72      !                                                       ! ==============
[1601]73      DO jn = 1, nn_nmax                                      ! Iterative loop
[16]74         !                                                    ! ==============
[3]75
[1601]76         IF( MOD(icount,ijpr2d+1) == 0 )   CALL lbc_lnk_e( gcx, c_solver_pt, 1. )   ! lateral boundary conditions
[784]77       
[16]78         ! Residus
79         ! -------
[86]80
81         ! Guess black update
[784]82         DO jj = 2-jpr2dj, nlcj-1+jpr2dj
83            ishift = MOD( jj-ijmppodd-jpr2dj, 2 )
84            DO ji = 2-jpr2di+ishift, nlci-1+jpr2di, 2
[86]85               ztmp =                  gcb(ji  ,jj  )   &
86                  &   - gcp(ji,jj,1) * gcx(ji  ,jj-1)   &
87                  &   - gcp(ji,jj,2) * gcx(ji-1,jj  )   &
88                  &   - gcp(ji,jj,3) * gcx(ji+1,jj  )   &
89                  &   - gcp(ji,jj,4) * gcx(ji  ,jj+1)
90               ! Estimate of the residual
[111]91               zres = ztmp - gcx(ji,jj)
[86]92               gcr(ji,jj) = zres * gcdmat(ji,jj) * zres
93               ! Guess update
[1601]94               gcx(ji,jj) = rn_sor * ztmp + (1-rn_sor) * gcx(ji,jj)
[3]95            END DO
96         END DO
[784]97         icount = icount + 1 
98 
[1601]99         IF( MOD(icount,ijpr2d+1) == 0 )   CALL lbc_lnk_e( gcx, c_solver_pt, 1. )   ! lateral boundary conditions
[3]100
[86]101         ! Guess red update
[784]102         DO jj = 2-jpr2dj, nlcj-1+jpr2dj
103            ishift = MOD( jj-ijmppeven-jpr2dj, 2 )
104            DO ji = 2-jpr2di+ishift, nlci-1+jpr2di, 2
[86]105               ztmp =                  gcb(ji  ,jj  )   &
106                  &   - gcp(ji,jj,1) * gcx(ji  ,jj-1)   &
107                  &   - gcp(ji,jj,2) * gcx(ji-1,jj  )   &
108                  &   - gcp(ji,jj,3) * gcx(ji+1,jj  )   &
109                  &   - gcp(ji,jj,4) * gcx(ji  ,jj+1) 
110               ! Estimate of the residual
[111]111               zres = ztmp - gcx(ji,jj)
[86]112               gcr(ji,jj) = zres * gcdmat(ji,jj) * zres
113               ! Guess update
[1601]114               gcx(ji,jj) = rn_sor * ztmp + (1-rn_sor) * gcx(ji,jj)
[3]115            END DO
116         END DO
[784]117         icount = icount + 1
[86]118
[111]119         ! test of convergence
[1601]120         IF ( jn > nn_nmin .AND. MOD( jn-nn_nmin, nn_nmod ) == 0 ) THEN
[86]121
[1601]122            SELECT CASE ( nn_sol_arp )
[120]123            CASE ( 0 )                 ! absolute precision (maximum value of the residual)
[784]124               zres2 = MAXVAL( gcr(2:nlci-1,2:nlcj-1) )
[120]125               IF( lk_mpp )   CALL mpp_max( zres2 )   ! max over the global domain
126               ! test of convergence
[1601]127               IF( zres2 < rn_resmax .OR. jn == nn_nmax ) THEN
[120]128                  res = SQRT( zres2 )
129                  niter = jn
130                  ncut = 999
131               ENDIF
[111]132            CASE ( 1 )                 ! relative precision
[784]133               rnorme = SUM( gcr(2:nlci-1,2:nlcj-1) )
[111]134               IF( lk_mpp )   CALL mpp_sum( rnorme )   ! sum over the global domain
135               ! test of convergence
[1601]136               IF( rnorme < epsr .OR. jn == nn_nmax ) THEN
[111]137                  res = SQRT( rnorme )
138                  niter = jn
139                  ncut = 999
140               ENDIF
[120]141            END SELECT
[3]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         
[111]148         ENDIF
[3]149         ! indicator of non-convergence or explosion
[1601]150         IF( jn == nn_nmax .OR. SQRT(epsr)/eps > 1.e+20 ) kindic = -2
[3]151         IF( ncut == 999 ) GOTO 999
152         
[16]153         !                                                 ! =====================
154      END DO                                               ! END of iterative loop
155      !                                                    ! =====================
[3]156     
157999   CONTINUE
158     
[16]159      !  Output in gcx
160      !  -------------
[784]161      CALL lbc_lnk_e( gcx, c_solver_pt, 1. )    ! boundary conditions
[1601]162      !
[3]163   END SUBROUTINE sol_sor
164
165   !!=====================================================================
166END MODULE solsor
Note: See TracBrowser for help on using the repository browser.