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

source: branches/dev_005_AWL/NEMO/OPA_SRC/SOL/solmat.F90 @ 1804

Last change on this file since 1804 was 1804, checked in by sga, 14 years ago

merge of trunk changes from r1782 to r1802 into NEMO branch dev_005_AWL

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 14.6 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
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
144      IF( .NOT. Agrif_Root() ) THEN   ! Fine grid boundaries
145         !
146         IF( nbondi == -1 .OR. nbondi == 2 )   bmask(2     ,:     ) = 0.e0
147         IF( nbondi ==  1 .OR. nbondi == 2 )   bmask(nlci-1,:     ) = 0.e0
148         IF( nbondj == -1 .OR. nbondj == 2 )   bmask(:     ,2     ) = 0.e0
149         IF( nbondj ==  1 .OR. nbondj == 2 )   bmask(:     ,nlcj-1) = 0.e0
150         !
151         DO jj = 2, jpjm1
152            DO ji = 2, jpim1
153               zcoef = z2dt * z2dt * grav * bmask(ji,jj)
154               !  south coefficient
155               IF( ( nbondj == -1 .OR. nbondj == 2 ) .AND. ( jj == 3 ) ) THEN
156                  zcoefs = -zcoef * hv(ji,jj-1) * e1v(ji,jj-1)/e2v(ji,jj-1)*(1.-vmask(ji,jj-1,1))
157               ELSE
158                  zcoefs = -zcoef * hv(ji,jj-1) * e1v(ji,jj-1)/e2v(ji,jj-1)
159               END IF
160               gcp(ji,jj,1) = zcoefs
161               !
162               !  west coefficient
163               IF( ( nbondi == -1 .OR. nbondi == 2 ) .AND. ( ji == 3 )  ) THEN
164                  zcoefw = -zcoef * hu(ji-1,jj) * e2u(ji-1,jj)/e1u(ji-1,jj)*(1.-umask(ji-1,jj,1))
165               ELSE
166                  zcoefw = -zcoef * hu(ji-1,jj) * e2u(ji-1,jj)/e1u(ji-1,jj)
167               END IF
168               gcp(ji,jj,2) = zcoefw
169               !
170               !   east coefficient
171               IF( ( nbondi == 1 .OR. nbondi == 2 ) .AND. ( ji == nlci-2 ) ) THEN
172                  zcoefe = -zcoef * hu(ji,jj) * e2u(ji,jj)/e1u(ji,jj)*(1.-umask(ji,jj,1))
173               ELSE
174                  zcoefe = -zcoef * hu(ji,jj) * e2u(ji,jj)/e1u(ji,jj)
175               END IF
176               gcp(ji,jj,3) = zcoefe
177               !
178               !   north coefficient
179               IF( ( nbondj == 1 .OR. nbondj == 2 ) .AND. ( jj == nlcj-2 ) ) THEN
180                  zcoefn = -zcoef * hv(ji,jj) * e1v(ji,jj)/e2v(ji,jj)*(1.-vmask(ji,jj,1))
181               ELSE
182                  zcoefn = -zcoef * hv(ji,jj) * e1v(ji,jj)/e2v(ji,jj)
183               END IF
184               gcp(ji,jj,4) = zcoefn
185               !
186               ! diagonal coefficient
187               gcdmat(ji,jj) = e1t(ji,jj)*e2t(ji,jj)*bmask(ji,jj)   &
188                  &            - zcoefs -zcoefw -zcoefe -zcoefn
189            END DO
190         END DO
191         !
192      ENDIF
193
194      ! 2. Boundary conditions
195      ! ----------------------
196     
197      ! Cyclic east-west boundary conditions
198      !     ji=2 is the column east of ji=jpim1 and reciprocally,
199      !     ji=jpim1 is the column west of ji=2
200      !     all the coef are already set to zero as bmask is initialized to
201      !     zero for ji=1 and ji=jpj in dommsk.
202     
203      ! Symetrical conditions
204      ! free surface: no specific action
205      ! bsf system: n-s gradient of bsf = 0 along j=2 (perhaps a bug !!!!!!)
206      ! the diagonal coefficient of the southern grid points must be modify to
207      ! account for the existence of the south symmetric bassin.
208     
209      ! North fold boundary condition
210      !     all the coef are already set to zero as bmask is initialized to
211      !     zero on duplicated lignes and portion of lignes
212     
213      ! 3. Preconditioned matrix
214      ! ------------------------
215     
216      ! SOR and PCG solvers
217      DO jj = 1, jpj
218         DO ji = 1, jpi
219            IF( bmask(ji,jj) /= 0.e0 )   gcdprc(ji,jj) = 1.e0 / gcdmat(ji,jj)
220         END DO
221      END DO
222         
223      gcp(:,:,1) = gcp(:,:,1) * gcdprc(:,:)
224      gcp(:,:,2) = gcp(:,:,2) * gcdprc(:,:)
225      gcp(:,:,3) = gcp(:,:,3) * gcdprc(:,:)
226      gcp(:,:,4) = gcp(:,:,4) * gcdprc(:,:)
227      IF( nn_solv == 2 )  gccd(:,:) = rn_sor * gcp(:,:,2)
228
229      IF( nn_solv == 2 .AND. MAX( jpr2di, jpr2dj ) > 0) THEN
230         CALL lbc_lnk_e( gcp   (:,:,1), c_solver_pt, 1. )   ! lateral boundary conditions
231         CALL lbc_lnk_e( gcp   (:,:,2), c_solver_pt, 1. )   ! lateral boundary conditions
232         CALL lbc_lnk_e( gcp   (:,:,3), c_solver_pt, 1. )   ! lateral boundary conditions
233         CALL lbc_lnk_e( gcp   (:,:,4), c_solver_pt, 1. )   ! lateral boundary conditions
234         CALL lbc_lnk_e( gcdprc(:,:)  , c_solver_pt, 1. )   ! lateral boundary conditions
235         CALL lbc_lnk_e( gcdmat(:,:)  , c_solver_pt, 1. )   ! lateral boundary conditions         
236         IF( npolj /= 0 ) CALL sol_exd( gcp , c_solver_pt ) ! switch northernelements
237      END IF
238   
239      ! 4. Initialization the arrays used in pcg
240      ! ----------------------------------------
241      gcb  (:,:) = 0.e0
242      gcr  (:,:) = 0.e0
243      gcdes(:,:) = 0.e0
244      gccd (:,:) = 0.e0
245      !
246   END SUBROUTINE sol_mat
247
248
249   SUBROUTINE sol_exd( pt3d, cd_type )
250      !!----------------------------------------------------------------------
251      !!                  ***  routine sol_exd  ***
252      !!                 
253      !! ** Purpose :   Reorder gcb coefficient on the extra outer  halo
254      !!                at north fold in case of T or F pivot
255      !!
256      !! ** Method  :   Perform a circular permutation of the coefficients on
257      !!                the total area strictly above the pivot point,
258      !!                and on the semi-row of the pivot point   
259      !!----------------------------------------------------------------------
260      CHARACTER(len=1) , INTENT( in ) ::   cd_type   ! define the nature of pt2d array grid-points
261         !                                           !  = T , U , V , F , W
262         !                                           !  = S : T-point, north fold treatment
263         !                                           !  = G : F-point, north fold treatment
264         !                                           !  = I : sea-ice velocity at F-point with index shift
265      REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj,4), INTENT(inout) ::   pt3d   ! 2D field to be treated
266      !!
267      INTEGER  ::   ji, jk   ! dummy loop indices
268      INTEGER  ::   iloc     ! temporary integers
269      REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj,4) ::   ztab   ! 2D workspace
270      !!----------------------------------------------------------------------
271
272      ztab = pt3d
273
274      SELECT CASE ( npolj )            ! north fold type
275      !
276      CASE ( 3 , 4 )                        !==  T pivot  ==!
277         iloc = jpiglo/2 +1 
278         !   
279         SELECT CASE ( cd_type )
280         !
281         CASE ( 'T', 'S', 'U', 'W' )
282            DO jk = 1, 4
283               DO ji = 1-jpr2di, nlci+jpr2di
284                  pt3d(ji,nlcj:nlcj+jpr2dj,jk) = ztab(ji,nlcj:nlcj+jpr2dj,jk+3-2*MOD(jk+3,4))           
285               END DO
286            END DO
287            DO jk =1, 4
288               DO ji = nlci+jpr2di, 1-jpr2di,  -1
289                  IF( ( ji .LT. mi0(iloc) .AND. mi0(iloc) /= 1 ) &
290                     & .OR. ( mi0(iloc) == jpi+1 ) ) EXIT
291                     pt3d(ji,nlcj-1,jk) = ztab(ji,nlcj-1,jk+3-2*MOD(jk+3,4))
292               END DO
293            END DO
294            !
295         CASE ( 'F' ,'G' , 'I', 'V' )
296            DO jk =1, 4
297               DO ji = 1-jpr2di, nlci+jpr2di
298                  pt3d(ji,nlcj-1:nlcj+jpr2dj,jk) = ztab(ji,nlcj-1:nlcj+jpr2dj,jk+3-2*MOD(jk+3,4))           
299               END DO
300            END DO
301            !
302         END SELECT   ! cd_type
303          !
304      CASE ( 5 , 6 )                        !==  F pivot  ==!
305         iloc=jpiglo/2
306         !
307         SELECT CASE (cd_type )
308         !
309         CASE ( 'T'  ,'S', 'U', 'W')
310            DO jk =1, 4
311               DO ji = 1-jpr2di, nlci+jpr2di
312                  pt3d(ji,nlcj:nlcj+jpr2dj,jk) = ztab(ji,nlcj:nlcj+jpr2dj,jk+3-2*MOD(jk+3,4))           
313               END DO
314            END DO
315            !
316         CASE ( 'F' ,'G' , 'I', 'V' )
317            DO jk =1, 4
318               DO ji = 1-jpr2di, nlci+jpr2di
319                  pt3d(ji,nlcj:nlcj+jpr2dj,jk) = ztab(ji,nlcj:nlcj+jpr2dj,jk+3-2*MOD(jk+3,4))           
320               END DO
321            END DO
322            DO jk =1, 4
323               DO ji = nlci+jpr2di, 1-jpr2di,  -1
324                  IF( ( ji .LT. mi0(iloc) .AND. mi0(iloc) /= 1 ) .OR. ( mi0(iloc) == jpi+1 ) )   EXIT
325                    pt3d(ji,nlcj-1,jk) = ztab(ji,nlcj-1,jk+3-2*MOD(jk+3,4))
326               END DO
327            END DO
328            !
329         END SELECT   ! cd_type
330         !
331      END SELECT   ! npolj
332      !   
333   END SUBROUTINE sol_exd
334
335   !!======================================================================
336END MODULE solmat
Note: See TracBrowser for help on using the repository browser.