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.
solmat.F90 in branches/DEV_r1784_mid_year_merge_2010/NEMO/OPA_SRC/SOL – NEMO

source: branches/DEV_r1784_mid_year_merge_2010/NEMO/OPA_SRC/SOL/solmat.F90 @ 1970

Last change on this file since 1970 was 1970, checked in by acc, 14 years ago

ticket #684 step 5: Add in changes from the trunk between revisions 1821 and 1879.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 14.8 KB
Line 
1MODULE solmat
2   !!======================================================================
3   !!                       ***  MODULE  solmat  ***
4   !! solver       : construction of the matrix
5   !!======================================================================
6   !! History :   1.0  ! 1988-04  (G. Madec)  Original code
7   !!                  ! 1993-03  (M. Guyon)  symetrical conditions
8   !!                  ! 1993-06  (M. Guyon)  suppress pointers
9   !!                  ! 1996-05  (G. Madec)  merge sor and pcg formulations
10   !!                  ! 1996-11  (A. Weaver)  correction to preconditioning
11   !!   NEMO      1.0  ! 1902-08  (G. Madec)  F90: Free form
12   !!              -   ! 1902-11  (C. Talandier, A-M. Treguier) Free surface & Open boundaries
13   !!             2.0  ! 2005-09  (R. Benshila)  add sol_exd for extra outer halo
14   !!              -   ! 2005-11  (V. Garnier) Surface pressure gradient organization
15   !!             3.2  ! 2009-06  (S. Masson)  distributed restart using iom
16   !!              -   ! 2009-07  (R. Benshila)  suppression of rigid-lid option
17   !!----------------------------------------------------------------------
18
19   !!----------------------------------------------------------------------
20   !!   sol_mat : Construction of the matrix of used by the elliptic solvers
21   !!   sol_exd :
22   !!----------------------------------------------------------------------
23   USE oce             ! ocean dynamics and active tracers
24   USE dom_oce         ! ocean space and time domain
25   USE sol_oce         ! ocean solver
26   USE phycst          ! physical constants
27   USE obc_oce         ! ocean open boundary conditions
28   USE lbclnk          ! lateral boudary conditions
29   USE lib_mpp         ! distributed memory computing
30   USE in_out_manager  ! I/O manager
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   sol_mat    ! routine called by inisol.F90
36
37   !!----------------------------------------------------------------------
38   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
39   !! $Id$
40   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
41   !!----------------------------------------------------------------------
42
43CONTAINS
44
45   SUBROUTINE sol_mat( kt )
46      !!----------------------------------------------------------------------
47      !!                  ***  ROUTINE sol_mat  ***
48      !!
49      !! ** Purpose :   Construction of the matrix of used by the elliptic
50      !!              solvers (either sor or pcg methods).
51      !!
52      !! ** Method  :   The matrix is built for the divergence of the transport
53      !!              system. a diagonal preconditioning matrix is also defined.
54      !!
55      !! ** Action  : - gcp    : extra-diagonal elements of the matrix
56      !!              - gcdmat : preconditioning matrix (diagonal elements)
57      !!              - gcdprc : inverse of the preconditioning matrix
58      !!----------------------------------------------------------------------
59      INTEGER, INTENT(in) :: kt
60      !!
61      INTEGER ::   ji, jj                    ! dummy loop indices
62      REAL(wp) ::   zcoefs, zcoefw, zcoefe, zcoefn  ! temporary scalars
63      REAL(wp) ::   z2dt, zcoef
64      !!----------------------------------------------------------------------
65
66     
67      ! 1. Construction of the matrix
68      ! -----------------------------
69      zcoef = 0.e0                          ! initialize to zero
70      gcp(:,:,1) = 0.e0
71      gcp(:,:,2) = 0.e0
72      gcp(:,:,3) = 0.e0
73      gcp(:,:,4) = 0.e0
74      !
75      gcdprc(:,:) = 0.e0
76      gcdmat(:,:) = 0.e0
77      !
78      IF( neuler == 0 .AND. kt == nit000 ) THEN   ;   z2dt = rdt
79      ELSE                                        ;   z2dt = 2. * rdt
80      ENDIF
81
82#if defined key_dynspg_flt && ! defined key_obc
83
84      DO jj = 2, jpjm1                      ! matrix of free surface elliptic system
85         DO ji = 2, jpim1
86            zcoef = z2dt * z2dt * grav * bmask(ji,jj)
87            zcoefs = -zcoef * hv(ji  ,jj-1) * e1v(ji  ,jj-1) / e2v(ji  ,jj-1)    ! south coefficient
88            zcoefw = -zcoef * hu(ji-1,jj  ) * e2u(ji-1,jj  ) / e1u(ji-1,jj  )    ! west coefficient
89            zcoefe = -zcoef * hu(ji  ,jj  ) * e2u(ji  ,jj  ) / e1u(ji  ,jj  )    ! east coefficient
90            zcoefn = -zcoef * hv(ji  ,jj  ) * e1v(ji  ,jj  ) / e2v(ji  ,jj  )    ! north coefficient
91            gcp(ji,jj,1) = zcoefs
92            gcp(ji,jj,2) = zcoefw
93            gcp(ji,jj,3) = zcoefe
94            gcp(ji,jj,4) = zcoefn
95            gcdmat(ji,jj) = e1t(ji,jj) * e2t(ji,jj) * bmask(ji,jj)    &          ! diagonal coefficient
96               &          - zcoefs -zcoefw -zcoefe -zcoefn
97         END DO
98      END DO
99     
100#  elif defined key_dynspg_flt && defined key_obc
101      IF( Agrif_Root() ) THEN
102         DO jj = 2, jpjm1                      ! matrix of free surface elliptic system with open boundaries
103            DO ji = 2, jpim1
104               zcoef = z2dt * z2dt * grav * bmask(ji,jj)
105               !                                    ! south coefficient
106               IF( lp_obc_south .AND. ( jj == njs0p1 ) ) THEN
107                  zcoefs = -zcoef * hv(ji,jj-1) * e1v(ji,jj-1)/e2v(ji,jj-1)*(1.-vsmsk(ji,1))
108               ELSE
109                  zcoefs = -zcoef * hv(ji,jj-1) * e1v(ji,jj-1)/e2v(ji,jj-1)
110               END IF
111               gcp(ji,jj,1) = zcoefs
112               !
113               !                                    ! west coefficient
114               IF( lp_obc_west  .AND. ( ji == niw0p1 ) ) THEN
115                  zcoefw = -zcoef * hu(ji-1,jj) * e2u(ji-1,jj)/e1u(ji-1,jj)*(1.-uwmsk(jj,1))
116               ELSE
117                  zcoefw = -zcoef * hu(ji-1,jj) * e2u(ji-1,jj)/e1u(ji-1,jj)
118               END IF
119               gcp(ji,jj,2) = zcoefw
120               !
121               !                                    ! east coefficient
122               IF( lp_obc_east  .AND. ( ji == nie0 ) ) THEN
123                  zcoefe = -zcoef * hu(ji,jj) * e2u(ji,jj)/e1u(ji,jj)*(1.-uemsk(jj,1))
124               ELSE
125                  zcoefe = -zcoef * hu(ji,jj) * e2u(ji,jj)/e1u(ji,jj)
126               END IF
127               gcp(ji,jj,3) = zcoefe
128               !
129               !                                    ! north coefficient
130               IF( lp_obc_north .AND. ( jj == njn0 ) ) THEN
131                  zcoefn = -zcoef * hv(ji,jj) * e1v(ji,jj)/e2v(ji,jj)*(1.-vnmsk(ji,1))
132               ELSE
133               zcoefn = -zcoef * hv(ji,jj) * e1v(ji,jj)/e2v(ji,jj)
134               END IF
135               gcp(ji,jj,4) = zcoefn
136               !
137               !                                    ! diagonal coefficient
138               gcdmat(ji,jj) = e1t(ji,jj)*e2t(ji,jj)*bmask(ji,jj)   &
139                  &            - zcoefs -zcoefw -zcoefe -zcoefn
140            END DO
141         END DO
142      ENDIF
143#endif
144
145#if defined key_agrif
146      IF( .NOT.AGRIF_ROOT() ) THEN
147         !
148         IF( nbondi == -1 .OR. nbondi == 2 )   bmask(2     ,:     ) = 0.e0
149         IF( nbondi ==  1 .OR. nbondi == 2 )   bmask(nlci-1,:     ) = 0.e0
150         IF( nbondj == -1 .OR. nbondj == 2 )   bmask(:     ,2     ) = 0.e0
151         IF( nbondj ==  1 .OR. nbondj == 2 )   bmask(:     ,nlcj-1) = 0.e0
152         !
153         DO jj = 2, jpjm1
154            DO ji = 2, jpim1
155               zcoef = z2dt * z2dt * grav * bmask(ji,jj)
156               !  south coefficient
157               IF( ( nbondj == -1 .OR. nbondj == 2 ) .AND. ( jj == 3 ) ) THEN
158                  zcoefs = -zcoef * hv(ji,jj-1) * e1v(ji,jj-1)/e2v(ji,jj-1)*(1.-vmask(ji,jj-1,1))
159               ELSE
160                  zcoefs = -zcoef * hv(ji,jj-1) * e1v(ji,jj-1)/e2v(ji,jj-1)
161               END IF
162               gcp(ji,jj,1) = zcoefs
163               !
164               !  west coefficient
165               IF( ( nbondi == -1 .OR. nbondi == 2 ) .AND. ( ji == 3 )  ) THEN
166                  zcoefw = -zcoef * hu(ji-1,jj) * e2u(ji-1,jj)/e1u(ji-1,jj)*(1.-umask(ji-1,jj,1))
167               ELSE
168                  zcoefw = -zcoef * hu(ji-1,jj) * e2u(ji-1,jj)/e1u(ji-1,jj)
169               END IF
170               gcp(ji,jj,2) = zcoefw
171               !
172               !   east coefficient
173               IF( ( nbondi == 1 .OR. nbondi == 2 ) .AND. ( ji == nlci-2 ) ) THEN
174                  zcoefe = -zcoef * hu(ji,jj) * e2u(ji,jj)/e1u(ji,jj)*(1.-umask(ji,jj,1))
175               ELSE
176                  zcoefe = -zcoef * hu(ji,jj) * e2u(ji,jj)/e1u(ji,jj)
177               END IF
178               gcp(ji,jj,3) = zcoefe
179               !
180               !   north coefficient
181               IF( ( nbondj == 1 .OR. nbondj == 2 ) .AND. ( jj == nlcj-2 ) ) THEN
182                  zcoefn = -zcoef * hv(ji,jj) * e1v(ji,jj)/e2v(ji,jj)*(1.-vmask(ji,jj,1))
183               ELSE
184                  zcoefn = -zcoef * hv(ji,jj) * e1v(ji,jj)/e2v(ji,jj)
185               END IF
186               gcp(ji,jj,4) = zcoefn
187               !
188               ! diagonal coefficient
189               gcdmat(ji,jj) = e1t(ji,jj)*e2t(ji,jj)*bmask(ji,jj)   &
190                  &            - zcoefs -zcoefw -zcoefe -zcoefn
191            END DO
192         END DO
193         !
194      ENDIF
195#endif
196
197      ! 2. Boundary conditions
198      ! ----------------------
199     
200      ! Cyclic east-west boundary conditions
201      !     ji=2 is the column east of ji=jpim1 and reciprocally,
202      !     ji=jpim1 is the column west of ji=2
203      !     all the coef are already set to zero as bmask is initialized to
204      !     zero for ji=1 and ji=jpj in dommsk.
205     
206      ! Symetrical conditions
207      ! free surface: no specific action
208      ! bsf system: n-s gradient of bsf = 0 along j=2 (perhaps a bug !!!!!!)
209      ! the diagonal coefficient of the southern grid points must be modify to
210      ! account for the existence of the south symmetric bassin.
211     
212      ! North fold boundary condition
213      !     all the coef are already set to zero as bmask is initialized to
214      !     zero on duplicated lignes and portion of lignes
215     
216      ! 3. Preconditioned matrix
217      ! ------------------------
218     
219      ! SOR and PCG solvers
220      DO jj = 1, jpj
221         DO ji = 1, jpi
222            IF( bmask(ji,jj) /= 0.e0 )   gcdprc(ji,jj) = 1.e0 / gcdmat(ji,jj)
223         END DO
224      END DO
225         
226      gcp(:,:,1) = gcp(:,:,1) * gcdprc(:,:)
227      gcp(:,:,2) = gcp(:,:,2) * gcdprc(:,:)
228      gcp(:,:,3) = gcp(:,:,3) * gcdprc(:,:)
229      gcp(:,:,4) = gcp(:,:,4) * gcdprc(:,:)
230      IF( nn_solv == 2 )  gccd(:,:) = rn_sor * gcp(:,:,2)
231
232      IF( nn_solv == 2 .AND. MAX( jpr2di, jpr2dj ) > 0) THEN
233         CALL lbc_lnk_e( gcp   (:,:,1), c_solver_pt, 1. )   ! lateral boundary conditions
234         CALL lbc_lnk_e( gcp   (:,:,2), c_solver_pt, 1. )   ! lateral boundary conditions
235         CALL lbc_lnk_e( gcp   (:,:,3), c_solver_pt, 1. )   ! lateral boundary conditions
236         CALL lbc_lnk_e( gcp   (:,:,4), c_solver_pt, 1. )   ! lateral boundary conditions
237         CALL lbc_lnk_e( gcdprc(:,:)  , c_solver_pt, 1. )   ! lateral boundary conditions
238         CALL lbc_lnk_e( gcdmat(:,:)  , c_solver_pt, 1. )   ! lateral boundary conditions         
239         IF( npolj /= 0 ) CALL sol_exd( gcp , c_solver_pt ) ! switch northernelements
240      END IF
241   
242      ! 4. Initialization the arrays used in pcg
243      ! ----------------------------------------
244      gcb  (:,:) = 0.e0
245      gcr  (:,:) = 0.e0
246      gcdes(:,:) = 0.e0
247      gccd (:,:) = 0.e0
248      !
249   END SUBROUTINE sol_mat
250
251
252   SUBROUTINE sol_exd( pt3d, cd_type )
253      !!----------------------------------------------------------------------
254      !!                  ***  routine sol_exd  ***
255      !!                 
256      !! ** Purpose :   Reorder gcb coefficient on the extra outer  halo
257      !!                at north fold in case of T or F pivot
258      !!
259      !! ** Method  :   Perform a circular permutation of the coefficients on
260      !!                the total area strictly above the pivot point,
261      !!                and on the semi-row of the pivot point   
262      !!----------------------------------------------------------------------
263      CHARACTER(len=1) , INTENT( in ) ::   cd_type   ! define the nature of pt2d array grid-points
264         !                                           !  = T , U , V , F , W
265         !                                           !  = S : T-point, north fold treatment
266         !                                           !  = G : F-point, north fold treatment
267         !                                           !  = I : sea-ice velocity at F-point with index shift
268      REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj,4), INTENT(inout) ::   pt3d   ! 2D field to be treated
269      !!
270      INTEGER  ::   ji, jk   ! dummy loop indices
271      INTEGER  ::   iloc     ! temporary integers
272      REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj,4) ::   ztab   ! 2D workspace
273      !!----------------------------------------------------------------------
274
275      ztab = pt3d
276
277      SELECT CASE ( npolj )            ! north fold type
278      !
279      CASE ( 3 , 4 )                        !==  T pivot  ==!
280         iloc = jpiglo/2 +1 
281         !   
282         SELECT CASE ( cd_type )
283         !
284         CASE ( 'T', 'S', 'U', 'W' )
285            DO jk = 1, 4
286               DO ji = 1-jpr2di, nlci+jpr2di
287                  pt3d(ji,nlcj:nlcj+jpr2dj,jk) = ztab(ji,nlcj:nlcj+jpr2dj,jk+3-2*MOD(jk+3,4))           
288               END DO
289            END DO
290            DO jk =1, 4
291               DO ji = nlci+jpr2di, 1-jpr2di,  -1
292                  IF( ( ji .LT. mi0(iloc) .AND. mi0(iloc) /= 1 ) &
293                     & .OR. ( mi0(iloc) == jpi+1 ) ) EXIT
294                     pt3d(ji,nlcj-1,jk) = ztab(ji,nlcj-1,jk+3-2*MOD(jk+3,4))
295               END DO
296            END DO
297            !
298         CASE ( 'F' ,'G' , 'I', 'V' )
299            DO jk =1, 4
300               DO ji = 1-jpr2di, nlci+jpr2di
301                  pt3d(ji,nlcj-1:nlcj+jpr2dj,jk) = ztab(ji,nlcj-1:nlcj+jpr2dj,jk+3-2*MOD(jk+3,4))           
302               END DO
303            END DO
304            !
305         END SELECT   ! cd_type
306          !
307      CASE ( 5 , 6 )                        !==  F pivot  ==!
308         iloc=jpiglo/2
309         !
310         SELECT CASE (cd_type )
311         !
312         CASE ( 'T'  ,'S', 'U', 'W')
313            DO jk =1, 4
314               DO ji = 1-jpr2di, nlci+jpr2di
315                  pt3d(ji,nlcj:nlcj+jpr2dj,jk) = ztab(ji,nlcj:nlcj+jpr2dj,jk+3-2*MOD(jk+3,4))           
316               END DO
317            END DO
318            !
319         CASE ( 'F' ,'G' , 'I', 'V' )
320            DO jk =1, 4
321               DO ji = 1-jpr2di, nlci+jpr2di
322                  pt3d(ji,nlcj:nlcj+jpr2dj,jk) = ztab(ji,nlcj:nlcj+jpr2dj,jk+3-2*MOD(jk+3,4))           
323               END DO
324            END DO
325            DO jk =1, 4
326               DO ji = nlci+jpr2di, 1-jpr2di,  -1
327                  IF( ( ji .LT. mi0(iloc) .AND. mi0(iloc) /= 1 ) .OR. ( mi0(iloc) == jpi+1 ) )   EXIT
328                    pt3d(ji,nlcj-1,jk) = ztab(ji,nlcj-1,jk+3-2*MOD(jk+3,4))
329               END DO
330            END DO
331            !
332         END SELECT   ! cd_type
333         !
334      END SELECT   ! npolj
335      !   
336   END SUBROUTINE sol_exd
337
338   !!======================================================================
339END MODULE solmat
Note: See TracBrowser for help on using the repository browser.