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

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

CT : UPDATE001 : First major NEMO update

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.1 KB
Line 
1MODULE solsor
2   !!======================================================================
3   !!                     ***  MODULE  solsor
4   !! Ocean solver :  Successive Over-Relaxation solver
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   sol_sor     : 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 successive-over-relaxation
38      !!      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      !!   8.5  !  02-08  (G. Madec)  F90: Free form
58      !!        !  03-02  (C. Deltel)  Red-Black SOR <== Not done yet!!!
59      !!                                                *************
60      !!----------------------------------------------------------------------
61      !! * Arguments
62      INTEGER, INTENT( inout ) ::   kindic   ! solver indicator, < 0 if the conver-
63      !                                      ! gence is not reached: the model is
64      !                                      ! stopped in step
65      !                                      ! set to zero before the call of solsor
66
67      !! * Local declarations
68      INTEGER  ::   ji, jj, jn               ! dummy loop indices
69      !!----------------------------------------------------------------------
70     
71      !                                                       ! ==============
72      DO jn = 1, nmax                                         ! Iterative loop
73         !                                                    ! ==============
74
75         CALL lbc_lnk( gcx, c_solver_pt, 1. )   ! applied the lateral boubary conditions
76         
77         ! Residus
78         ! -------
79         DO jj = 2, jpjm1
80            DO ji = 2, jpim1
81               gcr(ji,jj) =  gcb(ji,jj  ) -                gcx(ji  ,jj  )   &
82                                          - gcp(ji,jj,1) * gcx(ji  ,jj-1)   &
83                                          - gcp(ji,jj,2) * gcx(ji-1,jj  )   &
84                                          - gcp(ji,jj,3) * gcx(ji+1,jj  )   &
85                                          - gcp(ji,jj,4) * gcx(ji  ,jj+1)
86            END DO
87         END DO
88         CALL lbc_lnk( gcr, c_solver_pt, 1. )   ! applied the lateral boubary conditions
89
90         ! Successive over relaxation
91         DO jj = 2, jpj
92            DO ji = 1, jpi
93               gcr(ji,jj) = gcr(ji,jj) - sor * gcp(ji,jj,1) * gcr(ji,jj-1)
94            END DO
95            DO ji = 2, jpi
96               gcr(ji,jj) = gcr(ji,jj) - sor * gcp(ji,jj,2) * gcr(ji-1,jj)
97            END DO
98         END DO
99         
100         ! gcx guess
101         DO jj = 2, jpjm1
102            DO ji = 1, jpi
103               gcx(ji,jj)  = ( gcx(ji,jj) + sor * gcr(ji,jj) ) * bmask(ji,jj)
104            END DO
105         END DO
106         CALL lbc_lnk( gcx, c_solver_pt, 1. )
107         
108         ! relative precision
109         rnorme = SUM( gcr(:,:) * gcdmat(:,:) * gcr(:,:) )
110         IF( lk_mpp )   CALL mpp_sum( rnorme )   ! sum over the global domain
111         
112         ! test of convergence
113         ! old test (either res<resmax or jn=nmax)
114         !           IF( res < resmax .OR. jn == nmax ) THEN
115         ! relative precision
116         IF( rnorme < epsr .OR. jn == nmax ) THEN
117            res = SQRT( rnorme )
118            niter = jn
119            ncut = 999
120         ENDIF
121         
122         !****
123         !     IF(lwp)WRITE(numsol,9300) jn, res, sqrt( epsr ) / eps
1249300     FORMAT('          niter :',i4,' res :',e20.10,' b :',e20.10)
125         !****
126         
127         ! indicator of non-convergence or explosion
128         IF( jn == nmax .OR. SQRT(epsr)/eps > 1.e+20 ) kindic = -2
129         IF( ncut == 999 ) GOTO 999
130         
131         !                                                 ! =====================
132      END DO                                               ! END of iterative loop
133      !                                                    ! =====================
134     
135999   CONTINUE
136     
137     
138      !  Output in gcx
139      !  -------------
140     
141      CALL lbc_lnk( gcx, c_solver_pt, 1. )    ! boundary conditions (est-ce necessaire? je ne crois pas!!!!)
142     
143   END SUBROUTINE sol_sor
144
145   !!=====================================================================
146END MODULE solsor
Note: See TracBrowser for help on using the repository browser.