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/UKMO/dev_r5785_SSS_obsoper/NEMOGCM/NEMO/OPA_SRC/SOL – NEMO

source: branches/UKMO/dev_r5785_SSS_obsoper/NEMOGCM/NEMO/OPA_SRC/SOL/solmat.F90 @ 7740

Last change on this file since 7740 was 7740, checked in by mattmartin, 7 years ago

Removed svn keywords.

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