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.
domain.F90 in branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

source: branches/2013/dev_r3853_CNRS9_ConfSetting/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90 @ 3989

Last change on this file since 3989 was 3973, checked in by clevy, 11 years ago

Configuration setting/Step3, see ticket:#1074

  • Property svn:keywords set to Id
File size: 21.0 KB
Line 
1MODULE domain
2   !!==============================================================================
3   !!                       ***  MODULE domain   ***
4   !! Ocean initialization : domain initialization
5   !!==============================================================================
6   !! History :  OPA  !  1990-10  (C. Levy - G. Madec)  Original code
7   !!                 !  1992-01  (M. Imbard) insert time step initialization
8   !!                 !  1996-06  (G. Madec) generalized vertical coordinate
9   !!                 !  1997-02  (G. Madec) creation of domwri.F
10   !!                 !  2001-05  (E.Durand - G. Madec) insert closed sea
11   !!   NEMO     1.0  !  2002-08  (G. Madec)  F90: Free form and module
12   !!            2.0  !  2005-11  (V. Garnier) Surface pressure gradient organization
13   !!            3.3  !  2010-11  (G. Madec)  initialisation in C1D configuration
14   !!----------------------------------------------------------------------
15   
16   !!----------------------------------------------------------------------
17   !!   dom_init       : initialize the space and time domain
18   !!   dom_nam        : read and contral domain namelists
19   !!   dom_ctl        : control print for the ocean domain
20   !!----------------------------------------------------------------------
21   USE oce             ! ocean variables
22   USE dom_oce         ! domain: ocean
23   USE sbc_oce         ! surface boundary condition: ocean
24   USE phycst          ! physical constants
25   USE closea          ! closed seas
26   USE in_out_manager  ! I/O manager
27   USE lib_mpp         ! distributed memory computing library
28
29   USE domhgr          ! domain: set the horizontal mesh
30   USE domzgr          ! domain: set the vertical mesh
31   USE domstp          ! domain: set the time-step
32   USE dommsk          ! domain: set the mask system
33   USE domwri          ! domain: write the meshmask file
34   USE domvvl          ! variable volume
35   USE c1d             ! 1D vertical configuration
36   USE dyncor_c1d      ! Coriolis term (c1d case)         (cor_c1d routine)
37   USE timing          ! Timing
38   USE lbclnk          ! ocean lateral boundary condition (or mpp link)
39
40   IMPLICIT NONE
41   PRIVATE
42
43   PUBLIC   dom_init   ! called by opa.F90
44
45   !! * Substitutions
46#  include "domzgr_substitute.h90"
47   !!-------------------------------------------------------------------------
48   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
49   !! $Id$
50   !! Software governed by the CeCILL licence        (NEMOGCM/NEMO_CeCILL.txt)
51   !!-------------------------------------------------------------------------
52CONTAINS
53
54   SUBROUTINE dom_init
55      !!----------------------------------------------------------------------
56      !!                  ***  ROUTINE dom_init  ***
57      !!                   
58      !! ** Purpose :   Domain initialization. Call the routines that are
59      !!              required to create the arrays which define the space
60      !!              and time domain of the ocean model.
61      !!
62      !! ** Method  : - dom_msk: compute the masks from the bathymetry file
63      !!              - dom_hgr: compute or read the horizontal grid-point position
64      !!                         and scale factors, and the coriolis factor
65      !!              - dom_zgr: define the vertical coordinate and the bathymetry
66      !!              - dom_stp: defined the model time step
67      !!              - dom_wri: create the meshmask file if nmsh=1
68      !!              - 1D configuration, move Coriolis, u and v at T-point
69      !!----------------------------------------------------------------------
70      INTEGER ::   jk          ! dummy loop argument
71      INTEGER ::   iconf = 0   ! local integers
72      !!----------------------------------------------------------------------
73      !
74      IF( nn_timing == 1 )   CALL timing_start('dom_init')
75      !
76      IF(lwp) THEN
77         WRITE(numout,*)
78         WRITE(numout,*) 'dom_init : domain initialization'
79         WRITE(numout,*) '~~~~~~~~'
80      ENDIF
81      !
82                             CALL dom_nam      ! read namelist ( namrun, namdom, namcla )
83                             CALL dom_clo      ! Closed seas and lake
84                             CALL dom_hgr      ! Horizontal mesh
85                             CALL dom_zgr      ! Vertical mesh and bathymetry
86                             CALL dom_msk      ! Masks
87      IF( ln_sco )           CALL dom_stiff    ! Maximum stiffness ratio/hydrostatic consistency
88      IF( lk_vvl         )   CALL dom_vvl      ! Vertical variable mesh
89      !
90      IF( lk_c1d         )   CALL cor_c1d      ! 1D configuration: Coriolis set at T-point
91      !
92      hu(:,:) = 0._wp                          ! Ocean depth at U- and V-points
93      hv(:,:) = 0._wp
94      DO jk = 1, jpk
95         hu(:,:) = hu(:,:) + fse3u(:,:,jk) * umask(:,:,jk)
96         hv(:,:) = hv(:,:) + fse3v(:,:,jk) * vmask(:,:,jk)
97      END DO
98      !                                        ! Inverse of the local depth
99      hur(:,:) = 1._wp / ( hu(:,:) + 1._wp - umask(:,:,1) ) * umask(:,:,1)
100      hvr(:,:) = 1._wp / ( hv(:,:) + 1._wp - vmask(:,:,1) ) * vmask(:,:,1)
101
102                             CALL dom_stp      ! time step
103      IF( nmsh /= 0      )   CALL dom_wri      ! Create a domain file
104      IF( .NOT.ln_rstart )   CALL dom_ctl      ! Domain control
105      !
106      IF( nn_timing == 1 )   CALL timing_stop('dom_init')
107      !
108   END SUBROUTINE dom_init
109
110
111   SUBROUTINE dom_nam
112      !!----------------------------------------------------------------------
113      !!                     ***  ROUTINE dom_nam  ***
114      !!                   
115      !! ** Purpose :   read domaine namelists and print the variables.
116      !!
117      !! ** input   : - namrun namelist
118      !!              - namdom namelist
119      !!              - namcla namelist
120      !!              - namnc4 namelist   ! "key_netcdf4" only
121      !!----------------------------------------------------------------------
122      USE ioipsl
123      NAMELIST/namrun/ nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl,   &
124         &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock ,   &
125         &             nn_write, ln_dimgnnn, ln_mskland  , ln_clobber   , nn_chunksz
126      NAMELIST/namdom/ nn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh    , rn_hmin,   &
127         &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,            &
128         &             rn_rdtmax, rn_rdth     , nn_baro     , nn_closea
129      NAMELIST/namcla/ nn_cla
130#if defined key_netcdf4
131      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip
132#endif
133      INTEGER  ::   ios                 ! Local integer output status for namelist read
134      !!----------------------------------------------------------------------
135
136      REWIND( numnam_ref )              ! Namelist namrun in reference namelist : Parameters of the run
137      READ  ( numnam_ref, namrun, IOSTAT = ios, ERR = 901)
138901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namrun in reference namelist', lwp )
139
140      REWIND( numnam_cfg )              ! Namelist namrun in configuration namelist : Parameters of the run
141      READ  ( numnam_cfg, namrun, IOSTAT = ios, ERR = 902 )
142902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namrun in configuration namelist', lwp )
143      WRITE ( numond, namrun )
144      !
145      IF(lwp) THEN                  ! control print
146         WRITE(numout,*)
147         WRITE(numout,*) 'dom_nam  : domain initialization through namelist read'
148         WRITE(numout,*) '~~~~~~~ '
149         WRITE(numout,*) '   Namelist namrun'
150         WRITE(numout,*) '      configuration name              cp_cfg     = ', cp_cfg
151         WRITE(numout,*) '      configuration resolution        jp_cfg     = ', jp_cfg
152         WRITE(numout,*) '      experiment name for output      cn_exp     = ', cn_exp
153         WRITE(numout,*) '      job number                      nn_no      = ', nn_no
154         WRITE(numout,*) '      experiment name for output      cn_exp     = ', cn_exp
155         WRITE(numout,*) '      restart logical                 ln_rstart  = ', ln_rstart
156         WRITE(numout,*) '      control of time step            nn_rstctl  = ', nn_rstctl
157         WRITE(numout,*) '      number of the first time step   nn_it000   = ', nn_it000
158         WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend
159         WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0
160         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy
161         WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate
162         WRITE(numout,*) '      frequency of restart file       nn_stock   = ', nn_stock
163         WRITE(numout,*) '      frequency of output file        nn_write   = ', nn_write
164         WRITE(numout,*) '      multi file dimgout              ln_dimgnnn = ', ln_dimgnnn
165         WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland
166         WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber
167         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz = ', nn_chunksz
168      ENDIF
169
170      no = nn_no                    ! conversion DOCTOR names into model names (this should disappear soon)
171      cexper = cn_exp
172      nrstdt = nn_rstctl
173      nit000 = nn_it000
174      nitend = nn_itend
175      ndate0 = nn_date0
176      nleapy = nn_leapy
177      ninist = nn_istate
178      nstock = nn_stock
179      nwrite = nn_write
180
181
182      !                             ! control of output frequency
183      IF ( nstock == 0 .OR. nstock > nitend ) THEN
184         WRITE(ctmp1,*) 'nstock = ', nstock, ' it is forced to ', nitend
185         CALL ctl_warn( ctmp1 )
186         nstock = nitend
187      ENDIF
188      IF ( nwrite == 0 ) THEN
189         WRITE(ctmp1,*) 'nwrite = ', nwrite, ' it is forced to ', nitend
190         CALL ctl_warn( ctmp1 )
191         nwrite = nitend
192      ENDIF
193
194#if defined key_agrif
195      IF( Agrif_Root() ) THEN
196#endif
197      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL
198      CASE (  1 ) 
199         CALL ioconf_calendar('gregorian')
200         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "gregorian", i.e. leap year'
201      CASE (  0 )
202         CALL ioconf_calendar('noleap')
203         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "noleap", i.e. no leap year'
204      CASE ( 30 )
205         CALL ioconf_calendar('360d')
206         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "360d", i.e. 360 days in a year'
207      END SELECT
208#if defined key_agrif
209      ENDIF
210#endif
211
212      REWIND( numnam_ref )              ! Namelist namdom in reference namelist : space & time domain (bathymetry, mesh, timestep)
213      READ  ( numnam_ref, namdom, IOSTAT = ios, ERR = 903)
214903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in reference namelist', lwp )
215
216      REWIND( numnam_cfg )              ! Namelist namdom in configuration namelist : space & time domain (bathymetry, mesh, timestep)
217      READ  ( numnam_cfg, namdom, IOSTAT = ios, ERR = 904 )
218904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in configuration namelist', lwp )
219      WRITE ( numond, namdom )
220
221      IF(lwp) THEN
222         WRITE(numout,*)
223         WRITE(numout,*) '   Namelist namdom : space & time domain'
224         WRITE(numout,*) '      flag read/compute bathymetry      nn_bathy     = ', nn_bathy
225         WRITE(numout,*) '      min depth of the ocean    (>0) or    rn_hmin   = ', rn_hmin
226         WRITE(numout,*) '      min number of ocean level (<0)       '
227         WRITE(numout,*) '      minimum thickness of partial      rn_e3zps_min = ', rn_e3zps_min, ' (m)'
228         WRITE(numout,*) '         step level                     rn_e3zps_rat = ', rn_e3zps_rat
229         WRITE(numout,*) '      create mesh/mask file(s)          nn_msh       = ', nn_msh
230         WRITE(numout,*) '           = 0   no file created           '
231         WRITE(numout,*) '           = 1   mesh_mask                 '
232         WRITE(numout,*) '           = 2   mesh and mask             '
233         WRITE(numout,*) '           = 3   mesh_hgr, msh_zgr and mask'
234         WRITE(numout,*) '      ocean time step                      rn_rdt    = ', rn_rdt
235         WRITE(numout,*) '      asselin time filter parameter        rn_atfp   = ', rn_atfp
236         WRITE(numout,*) '      time-splitting: nb of sub time-step  nn_baro   = ', nn_baro
237         WRITE(numout,*) '      acceleration of converge             nn_acc    = ', nn_acc
238         WRITE(numout,*) '        nn_acc=1: surface tracer rdt       rn_rdtmin = ', rn_rdtmin
239         WRITE(numout,*) '                  bottom  tracer rdt       rdtmax    = ', rn_rdtmax
240         WRITE(numout,*) '                  depth of transition      rn_rdth   = ', rn_rdth
241         WRITE(numout,*) '      suppression of closed seas (=0)      nn_closea = ', nn_closea
242      ENDIF
243
244      ntopo     = nn_bathy          ! conversion DOCTOR names into model names (this should disappear soon)
245      e3zps_min = rn_e3zps_min
246      e3zps_rat = rn_e3zps_rat
247      nmsh      = nn_msh
248      nacc      = nn_acc
249      atfp      = rn_atfp
250      rdt       = rn_rdt
251      rdtmin    = rn_rdtmin
252      rdtmax    = rn_rdtmin
253      rdth      = rn_rdth
254
255      REWIND( numnam_ref )              ! Namelist namcla in reference namelist : Cross land advection
256      READ  ( numnam_ref, namcla, IOSTAT = ios, ERR = 905)
257905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcla in reference namelist', lwp )
258
259      REWIND( numnam_cfg )              ! Namelist namcla in configuration namelist : Cross land advection
260      READ  ( numnam_cfg, namcla, IOSTAT = ios, ERR = 906 )
261906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcla in configuration namelist', lwp )
262      WRITE( numond, namcla )
263
264      IF(lwp) THEN
265         WRITE(numout,*)
266         WRITE(numout,*) '   Namelist namcla'
267         WRITE(numout,*) '      cross land advection                 nn_cla    = ', nn_cla
268      ENDIF
269      IF ( nn_cla .EQ. 1 ) THEN
270         IF  ( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN   ! ORCA R2
271            CONTINUE
272         ELSE
273            CALL ctl_stop( 'STOP', 'Cross land advation iplemented only for ORCA2 configuration: cp_cfg = "orca" and jp_cfg = 2 ' )
274         ENDIF
275      ENDIF
276
277#if defined key_netcdf4
278      !                             ! NetCDF 4 case   ("key_netcdf4" defined)
279      REWIND( numnam_ref )              ! Namelist namnc4 in reference namelist : NETCDF
280      READ  ( numnam_ref, namnc4, IOSTAT = ios, ERR = 907)
281907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namnc4 in reference namelist', lwp )
282
283      REWIND( numnam_cfg )              ! Namelist namnc4 in configuration namelist : NETCDF
284      READ  ( numnam_cfg, namnc4, IOSTAT = ios, ERR = 908 )
285908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namnc4 in configuration namelist', lwp )
286      WRITE( numond, namnc4 )
287
288      IF(lwp) THEN                        ! control print
289         WRITE(numout,*)
290         WRITE(numout,*) '   Namelist namnc4 - Netcdf4 chunking parameters'
291         WRITE(numout,*) '      number of chunks in i-dimension      nn_nchunks_i   = ', nn_nchunks_i
292         WRITE(numout,*) '      number of chunks in j-dimension      nn_nchunks_j   = ', nn_nchunks_j
293         WRITE(numout,*) '      number of chunks in k-dimension      nn_nchunks_k   = ', nn_nchunks_k
294         WRITE(numout,*) '      apply netcdf4/hdf5 chunking & compression ln_nc4zip = ', ln_nc4zip
295      ENDIF
296
297      ! Put the netcdf4 settings into a simple structure (snc4set, defined in in_out_manager module)
298      ! Note the chunk size in the unlimited (time) dimension will be fixed at 1
299      snc4set%ni   = nn_nchunks_i
300      snc4set%nj   = nn_nchunks_j
301      snc4set%nk   = nn_nchunks_k
302      snc4set%luse = ln_nc4zip
303#else
304      snc4set%luse = .FALSE.        ! No NetCDF 4 case
305#endif
306      !
307   END SUBROUTINE dom_nam
308
309
310   SUBROUTINE dom_ctl
311      !!----------------------------------------------------------------------
312      !!                     ***  ROUTINE dom_ctl  ***
313      !!
314      !! ** Purpose :   Domain control.
315      !!
316      !! ** Method  :   compute and print extrema of masked scale factors
317      !!----------------------------------------------------------------------
318      INTEGER ::   iimi1, ijmi1, iimi2, ijmi2, iima1, ijma1, iima2, ijma2
319      INTEGER, DIMENSION(2) ::   iloc   !
320      REAL(wp) ::   ze1min, ze1max, ze2min, ze2max
321      !!----------------------------------------------------------------------
322      !
323      IF(lk_mpp) THEN
324         CALL mpp_minloc( e1t(:,:), tmask(:,:,1), ze1min, iimi1,ijmi1 )
325         CALL mpp_minloc( e2t(:,:), tmask(:,:,1), ze2min, iimi2,ijmi2 )
326         CALL mpp_maxloc( e1t(:,:), tmask(:,:,1), ze1max, iima1,ijma1 )
327         CALL mpp_maxloc( e2t(:,:), tmask(:,:,1), ze2max, iima2,ijma2 )
328      ELSE
329         ze1min = MINVAL( e1t(:,:), mask = tmask(:,:,1) == 1._wp )   
330         ze2min = MINVAL( e2t(:,:), mask = tmask(:,:,1) == 1._wp )   
331         ze1max = MAXVAL( e1t(:,:), mask = tmask(:,:,1) == 1._wp )   
332         ze2max = MAXVAL( e2t(:,:), mask = tmask(:,:,1) == 1._wp )   
333
334         iloc  = MINLOC( e1t(:,:), mask = tmask(:,:,1) == 1._wp )
335         iimi1 = iloc(1) + nimpp - 1
336         ijmi1 = iloc(2) + njmpp - 1
337         iloc  = MINLOC( e2t(:,:), mask = tmask(:,:,1) == 1._wp )
338         iimi2 = iloc(1) + nimpp - 1
339         ijmi2 = iloc(2) + njmpp - 1
340         iloc  = MAXLOC( e1t(:,:), mask = tmask(:,:,1) == 1._wp )
341         iima1 = iloc(1) + nimpp - 1
342         ijma1 = iloc(2) + njmpp - 1
343         iloc  = MAXLOC( e2t(:,:), mask = tmask(:,:,1) == 1._wp )
344         iima2 = iloc(1) + nimpp - 1
345         ijma2 = iloc(2) + njmpp - 1
346      ENDIF
347      IF(lwp) THEN
348         WRITE(numout,*)
349         WRITE(numout,*) 'dom_ctl : extrema of the masked scale factors'
350         WRITE(numout,*) '~~~~~~~'
351         WRITE(numout,"(14x,'e1t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1max, iima1, ijma1
352         WRITE(numout,"(14x,'e1t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1min, iimi1, ijmi1
353         WRITE(numout,"(14x,'e2t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2max, iima2, ijma2
354         WRITE(numout,"(14x,'e2t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2min, iimi2, ijmi2
355      ENDIF
356      !
357   END SUBROUTINE dom_ctl
358
359   SUBROUTINE dom_stiff
360      !!----------------------------------------------------------------------
361      !!                  ***  ROUTINE dom_stiff  ***
362      !!                     
363      !! ** Purpose :   Diagnose maximum grid stiffness/hydrostatic consistency
364      !!
365      !! ** Method  :   Compute Haney (1991) hydrostatic condition ratio
366      !!                Save the maximum in the vertical direction
367      !!                (this number is only relevant in s-coordinates)
368      !!
369      !!                Haney, R. L., 1991: On the pressure gradient force
370      !!                over steep topography in sigma coordinate ocean models.
371      !!                J. Phys. Oceanogr., 21, 610???619.
372      !!----------------------------------------------------------------------
373      INTEGER  ::   ji, jj, jk 
374      REAL(wp) ::   zrxmax
375      REAL(wp), DIMENSION(4) :: zr1
376      !!----------------------------------------------------------------------
377      rx1(:,:) = 0.e0
378      zrxmax   = 0.e0
379      zr1(:)   = 0.e0
380     
381      DO ji = 2, jpim1
382         DO jj = 2, jpjm1
383            DO jk = 1, jpkm1
384               zr1(1) = umask(ji-1,jj  ,jk) *abs( (gdepw(ji  ,jj  ,jk  )-gdepw(ji-1,jj  ,jk  )  & 
385                    &                         +gdepw(ji  ,jj  ,jk+1)-gdepw(ji-1,jj  ,jk+1)) &
386                    &                        /(gdepw(ji  ,jj  ,jk  )+gdepw(ji-1,jj  ,jk  )  &
387                    &                         -gdepw(ji  ,jj  ,jk+1)-gdepw(ji-1,jj  ,jk+1) + rsmall) )
388               zr1(2) = umask(ji  ,jj  ,jk) *abs( (gdepw(ji+1,jj  ,jk  )-gdepw(ji  ,jj  ,jk  )  &
389                    &                         +gdepw(ji+1,jj  ,jk+1)-gdepw(ji  ,jj  ,jk+1)) &
390                    &                        /(gdepw(ji+1,jj  ,jk  )+gdepw(ji  ,jj  ,jk  )  &
391                    &                         -gdepw(ji+1,jj  ,jk+1)-gdepw(ji  ,jj  ,jk+1) + rsmall) )
392               zr1(3) = vmask(ji  ,jj  ,jk) *abs( (gdepw(ji  ,jj+1,jk  )-gdepw(ji  ,jj  ,jk  )  &
393                    &                         +gdepw(ji  ,jj+1,jk+1)-gdepw(ji  ,jj  ,jk+1)) &
394                    &                        /(gdepw(ji  ,jj+1,jk  )+gdepw(ji  ,jj  ,jk  )  &
395                    &                         -gdepw(ji  ,jj+1,jk+1)-gdepw(ji  ,jj  ,jk+1) + rsmall) )
396               zr1(4) = vmask(ji  ,jj-1,jk) *abs( (gdepw(ji  ,jj  ,jk  )-gdepw(ji  ,jj-1,jk  )  &
397                    &                         +gdepw(ji  ,jj  ,jk+1)-gdepw(ji  ,jj-1,jk+1)) &
398                    &                        /(gdepw(ji  ,jj  ,jk  )+gdepw(ji  ,jj-1,jk  )  &
399                    &                         -gdepw(ji,  jj  ,jk+1)-gdepw(ji  ,jj-1,jk+1) + rsmall) )
400               zrxmax = MAXVAL(zr1(1:4))
401               rx1(ji,jj) = MAX(rx1(ji,jj), zrxmax)
402            END DO
403         END DO
404      END DO
405
406      CALL lbc_lnk( rx1, 'T', 1. )
407
408      zrxmax = MAXVAL(rx1)
409
410      IF( lk_mpp )   CALL mpp_max( zrxmax ) ! max over the global domain
411
412      IF(lwp) THEN
413         WRITE(numout,*)
414         WRITE(numout,*) 'dom_stiff : maximum grid stiffness ratio: ', zrxmax
415         WRITE(numout,*) '~~~~~~~~~'
416      ENDIF
417
418   END SUBROUTINE dom_stiff
419
420
421
422   !!======================================================================
423END MODULE domain
Note: See TracBrowser for help on using the repository browser.