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.
domqe.F90 in NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/DOM – NEMO

source: NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/DOM/domqe.F90 @ 12581

Last change on this file since 12581 was 12581, checked in by techene, 4 years ago

OCE/DOM/domqe.F90: make dom_qe_r3c public, OCE/DYN/dynatfLF.F90: duplicate dynatf and replace dom_qe_interpol calls by the ssh scaling method to compute and update e3t/u/v at time Kmm, OCE/TRA/traatfLF.F90: duplicate traatf and replace dom_qe_interpol by the ssh scaling method to compute internal ze3t, OCE/steplf.F90: change the order of atf routines ssh_atf is called first then dom_qe_r3c to computed filtered ssh to h ratios at T-, U-, V-points finally tra_atf_lf and dyn_atf_lf

File size: 41.8 KB
Line 
1MODULE domqe
2   !!======================================================================
3   !!                       ***  MODULE domqe   ***
4   !! Ocean :
5   !!======================================================================
6   !! History :  2.0  !  2006-06  (B. Levier, L. Marie)  original code
7   !!            3.1  !  2009-02  (G. Madec, M. Leclair, R. Benshila)  pure z* coordinate
8   !!            3.3  !  2011-10  (M. Leclair) totally rewrote domvvl: vvl option includes z_star and z_tilde coordinates
9   !!            3.6  !  2014-11  (P. Mathiot) add ice shelf capability
10   !!            4.1  !  2019-08  (A. Coward, D. Storkey) rename dom_vvl_sf_swp -> dom_vvl_sf_update for new timestepping
11   !!            4.x  ! 2020-02  (G. Madec, S. Techene) pure z* (quasi-eulerian) coordinate
12   !!----------------------------------------------------------------------
13
14   !!----------------------------------------------------------------------
15   !!   dom_vvl_init     : define initial vertical scale factors, depths and column thickness
16   !!   dom_vvl_sf_nxt   : Compute next vertical scale factors
17   !!   dom_vvl_sf_update   : Swap vertical scale factors and update the vertical grid
18   !!   dom_vvl_interpol : Interpolate vertical scale factors from one grid point to another
19   !!   dom_vvl_r3c      : Compute ssh/h_0 ratioat t-, u-, v-, and optionally f-points
20   !!   dom_vvl_rst      : read/write restart file
21   !!   dom_vvl_ctl      : Check the vvl options
22   !!----------------------------------------------------------------------
23   USE oce             ! ocean dynamics and tracers
24   USE phycst          ! physical constant
25   USE dom_oce         ! ocean space and time domain
26   USE dynadv  , ONLY : ln_dynadv_vec
27   USE isf_oce         ! iceshelf cavities
28   USE sbc_oce         ! ocean surface boundary condition
29   USE wet_dry         ! wetting and drying
30   USE usrdef_istate   ! user defined initial state (wad only)
31   USE restart         ! ocean restart
32   !
33   USE in_out_manager  ! I/O manager
34   USE iom             ! I/O manager library
35   USE lib_mpp         ! distributed memory computing library
36   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
37   USE timing          ! Timing
38
39   IMPLICIT NONE
40   PRIVATE
41
42   PUBLIC  dom_qe_init       ! called by domain.F90
43   PUBLIC  dom_qe_zgr        ! called by isfcpl.F90
44   PUBLIC  dom_qe_sf_nxt     ! called by step.F90
45   PUBLIC  dom_qe_sf_update  ! called by step.F90
46   PUBLIC  dom_qe_interpol   ! called by dynnxt.F90
47   PUBLIC  dom_qe_r3c        ! called by steplf.F90
48
49   !                                                      !!* Namelist nam_vvl
50   LOGICAL , PUBLIC :: ln_vvl_zstar           = .FALSE.    ! zstar  vertical coordinate
51   LOGICAL , PUBLIC :: ln_vvl_ztilde          = .FALSE.    ! ztilde vertical coordinate
52   LOGICAL , PUBLIC :: ln_vvl_layer           = .FALSE.    ! level  vertical coordinate
53   LOGICAL , PUBLIC :: ln_vvl_ztilde_as_zstar = .FALSE.    ! ztilde vertical coordinate
54   LOGICAL , PUBLIC :: ln_vvl_zstar_at_eqtor  = .FALSE.    ! ztilde vertical coordinate
55   LOGICAL , PUBLIC :: ln_vvl_kepe            = .FALSE.    ! kinetic/potential energy transfer
56   !                                                       ! conservation: not used yet
57   REAL(wp)         :: rn_ahe3                             ! thickness diffusion coefficient
58   REAL(wp)         :: rn_rst_e3t                          ! ztilde to zstar restoration timescale [days]
59   REAL(wp)         :: rn_lf_cutoff                        ! cutoff frequency for low-pass filter  [days]
60   REAL(wp)         :: rn_zdef_max                         ! maximum fractional e3t deformation
61   LOGICAL , PUBLIC :: ln_vvl_dbg = .FALSE.                ! debug control prints
62
63   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: un_td, vn_td                ! thickness diffusion transport
64
65   !! * Substitutions
66#  include "do_loop_substitute.h90"
67   !!----------------------------------------------------------------------
68   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
69   !! $Id: domvvl.F90 12377 2020-02-12 14:39:06Z acc $
70   !! Software governed by the CeCILL license (see ./LICENSE)
71   !!----------------------------------------------------------------------
72CONTAINS
73
74   SUBROUTINE dom_qe_init( Kbb, Kmm, Kaa )
75      !!----------------------------------------------------------------------
76      !!                ***  ROUTINE dom_qe_init  ***
77      !!
78      !! ** Purpose :  Initialization of all scale factors, depths
79      !!               and water column heights
80      !!
81      !! ** Method  :  - use restart file and/or initialize
82      !!               - interpolate scale factors
83      !!
84      !! ** Action  : - e3t_(n/b)
85      !!              - Regrid: e3[u/v](:,:,:,Kmm)
86      !!                        e3[u/v](:,:,:,Kmm)
87      !!                        e3w(:,:,:,Kmm)
88      !!                        e3[u/v]w_b
89      !!                        e3[u/v]w_n
90      !!                        gdept(:,:,:,Kmm), gdepw(:,:,:,Kmm) and gde3w
91      !!              - h(t/u/v)_0
92      !!
93      !! Reference  : Leclair, M., and G. Madec, 2011, Ocean Modelling.
94      !!----------------------------------------------------------------------
95      INTEGER, INTENT(in) :: Kbb, Kmm, Kaa
96      !
97      IF(lwp) WRITE(numout,*)
98      IF(lwp) WRITE(numout,*) 'dom_qe_init : Variable volume activated'
99      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
100      !
101      CALL dom_qe_ctl     ! choose vertical coordinate (z_star, z_tilde or layer)
102      !
103      !                    ! Read or initialize e3t_(b/n), tilde_e3t_(b/n) and hdiv_lf
104      CALL dom_qe_rst( nit000, Kbb, Kmm, 'READ' )
105      e3t(:,:,jpk,Kaa) = e3t_0(:,:,jpk)  ! last level always inside the sea floor set one for all
106      !
107      CALL dom_qe_zgr(Kbb, Kmm, Kaa) ! interpolation scale factor, depth and water column
108      !
109      IF(lwxios) THEN   ! define variables in restart file when writing with XIOS
110         CALL iom_set_rstw_var_active('e3t_b')
111         CALL iom_set_rstw_var_active('e3t_n')
112      ENDIF
113      !
114   END SUBROUTINE dom_qe_init
115
116
117   SUBROUTINE dom_qe_zgr(Kbb, Kmm, Kaa)
118      !!----------------------------------------------------------------------
119      !!                ***  ROUTINE dom_qe_init  ***
120      !!
121      !! ** Purpose :  Interpolation of all scale factors,
122      !!               depths and water column heights
123      !!
124      !! ** Method  :  - interpolate scale factors
125      !!
126      !! ** Action  : - e3t_(n/b)
127      !!              - Regrid: e3(u/v)_n
128      !!                        e3(u/v)_b
129      !!                        e3w_n
130      !!                        e3(u/v)w_b
131      !!                        e3(u/v)w_n
132      !!                        gdept_n, gdepw_n and gde3w_n
133      !!              - h(t/u/v)_0
134      !!
135      !! Reference  : Leclair, M., and G. Madec, 2011, Ocean Modelling.
136      !!----------------------------------------------------------------------
137      INTEGER, INTENT(in) :: Kbb, Kmm, Kaa
138      !!----------------------------------------------------------------------
139      INTEGER ::   ji, jj, jk
140      INTEGER ::   ii0, ii1, ij0, ij1
141      REAL(wp)::   zcoef
142      !!----------------------------------------------------------------------
143      !
144      !                    !== Set of all other vertical scale factors  ==!  (now and before)
145      !                                ! Horizontal interpolation of e3t
146      CALL dom_qe_r3c( ssh(:,:,Kbb), r3t(:,:,Kbb), r3u(:,:,Kbb), r3v(:,:,Kbb) )
147      CALL dom_qe_r3c( ssh(:,:,Kmm), r3t(:,:,Kmm), r3u(:,:,Kmm), r3v(:,:,Kmm), r3f(:,:) )
148      !
149      DO jk = 1, jpkm1                    ! Horizontal interpolation of e3t
150         e3t(:,:,jk,Kbb) = e3t_0(:,:,jk) * ( 1._wp + r3t(:,:,Kbb) * tmask(:,:,jk) )   ! Kbb time level
151         e3u(:,:,jk,Kbb) = e3u_0(:,:,jk) * ( 1._wp + r3u(:,:,Kbb) * umask(:,:,jk) )
152         e3v(:,:,jk,Kbb) = e3v_0(:,:,jk) * ( 1._wp + r3v(:,:,Kbb) * vmask(:,:,jk) )
153         e3t(:,:,jk,Kmm) = e3t_0(:,:,jk) * ( 1._wp + r3t(:,:,Kmm) * tmask(:,:,jk) )   ! Kmm time level
154         e3u(:,:,jk,Kmm) = e3u_0(:,:,jk) * ( 1._wp + r3u(:,:,Kmm) * umask(:,:,jk) )
155         e3v(:,:,jk,Kmm) = e3v_0(:,:,jk) * ( 1._wp + r3v(:,:,Kmm) * vmask(:,:,jk) )
156         e3f(:,:,jk)     = e3f_0(:,:,jk) * ( 1._wp + r3f(:,:)     * fmask(:,:,jk) )
157      END DO
158      !
159      DO jk = 1, jpk                      ! Vertical interpolation of e3t,u,v
160         !                                   ! The ratio does not have to be masked at w-level
161         e3w (:,:,jk,Kbb) =  e3w_0(:,:,jk) * ( 1._wp + r3t(:,:,Kbb) )   ! Kbb time level
162         e3uw(:,:,jk,Kbb) = e3uw_0(:,:,jk) * ( 1._wp + r3u(:,:,Kbb) )
163         e3vw(:,:,jk,Kbb) = e3vw_0(:,:,jk) * ( 1._wp + r3v(:,:,Kbb) )
164         e3w (:,:,jk,Kmm) =  e3w_0(:,:,jk) * ( 1._wp + r3t(:,:,Kmm) )   ! Kmm time level
165         e3uw(:,:,jk,Kmm) = e3uw_0(:,:,jk) * ( 1._wp + r3u(:,:,Kmm) )
166         e3vw(:,:,jk,Kmm) = e3vw_0(:,:,jk) * ( 1._wp + r3v(:,:,Kmm) )
167      END DO
168      !
169      ! We need to define e3[tuv]_a for AGRIF initialisation (should not be a problem for the restartability...)
170      e3t(:,:,:,Kaa) = e3t(:,:,:,Kmm)
171      e3u(:,:,:,Kaa) = e3u(:,:,:,Kmm)
172      e3v(:,:,:,Kaa) = e3v(:,:,:,Kmm)
173      !
174      !                    !==  depth of t and w-point  ==!   (set the isf depth as it is in the initial timestep)
175      IF( ln_isf ) THEN          !** IceShelF cavities
176      !                             ! to be created depending of the new names in isf
177      !                             ! it should be something like that :  (with h_isf = thickness of iceshelf)
178      !                             !  in fact currently, h_isf(:,:) is called : risfdep(:,:)
179!!gm - depth idea 0  : just realize that mask is not needed ===>>>> with ISF, rescale all grid point position below ISF : no mask !
180         gdept(:,:,1,Kmm) = gdept_0(:,:,1) * ( 1._wp + r3t(:,:,Kmm) )
181         gdepw(:,:,1,Kmm) = 0._wp                            ! Initialized to zero one for all
182         gde3w(:,:,1)     = gdept(:,:,1,Kmm) - ssh(:,:,Kmm)  ! reference to a common level z=0 for hpg
183         DO jk = 2, jpk
184            gdept(:,:,jk,Kmm) = MIN( risfdep(:,:) , gdept_0(:,:,jk) )            &
185                              + MAX(   0._wp    , gdept_0(:,:,jk)-risfdep(:,:) ) * ( 1._wp + r3t(:,:,Kmm) )
186            gdepw(:,:,jk,Kmm) = MIN( risfdep(:,:) , gdepw_0(:,:,jk) )    &
187                              + MAX(   0._wp    , gdepw_0(:,:,jk)-risfdep(:,:) ) * ( 1._wp + r3t(:,:,Kmm) )
188            gde3w(:,:,jk)     = gdept(:,:,jk,Kmm) - ssh(:,:,Kmm)
189            gdept(:,:,jk,Kbb) = MIN( risfdep(:,:) , gdept_0(:,:,jk) )            &
190                              + MAX(   0._wp    , gdept_0(:,:,jk)-risfdep(:,:) ) * ( 1._wp + r3t(:,:,Kbb) )
191            gdepw(:,:,jk,Kbb) = MIN( risfdep(:,:) , gdepw_0(:,:,jk) )    &
192                              + MAX(   0._wp    , gdepw_0(:,:,jk)-risfdep(:,:) ) * ( 1._wp + r3t(:,:,Kbb) )
193         END DO
194         !
195      ELSE                       !** No cavities   (all depth rescaled, even inside topography: no mask)
196         !
197!!gm idea 0 :   just realize that mask is not needed ===>>>> without ISF, rescale all grid point position : no mask !
198         DO jk = 1, jpk
199            gdept(:,:,jk,Kmm) = gdept_0(:,:,jk) * ( 1._wp + r3t(:,:,Kmm) )
200            gdepw(:,:,jk,Kmm) = gdepw_0(:,:,jk) * ( 1._wp + r3t(:,:,Kmm) )
201            gde3w(:,:,jk)     = gdept  (:,:,jk,Kmm)       - ssh(:,:,Kmm)
202            gdept(:,:,jk,Kbb) = gdept_0(:,:,jk) * ( 1._wp + r3t(:,:,Kbb) )
203            gdepw(:,:,jk,Kbb) = gdepw_0(:,:,jk) * ( 1._wp + r3t(:,:,Kbb) )
204         END DO
205         !
206      ENDIF
207      !
208      !                    !==  thickness of the water column  !!   (ocean portion only)
209      ht(:,:)     = ht_0(:,:)           + ssh(:,:,Kmm)
210      hu(:,:,Kbb) = hu_0(:,:) * ( 1._wp + r3u(:,:,Kbb) )
211      hu(:,:,Kmm) = hu_0(:,:) * ( 1._wp + r3u(:,:,Kmm) )
212      hv(:,:,Kbb) = hv_0(:,:) * ( 1._wp + r3v(:,:,Kbb) )
213      hv(:,:,Kmm) = hv_0(:,:) * ( 1._wp + r3v(:,:,Kmm) )
214      !
215      !                    !==  inverse of water column thickness   ==!   (u- and v- points)
216      r1_hu(:,:,Kbb) = ssumask(:,:) / ( hu(:,:,Kbb) + 1._wp - ssumask(:,:) )    ! _i mask due to ISF
217      r1_hu(:,:,Kmm) = ssumask(:,:) / ( hu(:,:,Kmm) + 1._wp - ssumask(:,:) )
218      r1_hv(:,:,Kbb) = ssvmask(:,:) / ( hv(:,:,Kbb) + 1._wp - ssvmask(:,:) )
219      r1_hv(:,:,Kmm) = ssvmask(:,:) / ( hv(:,:,Kmm) + 1._wp - ssvmask(:,:) )
220      !
221   END SUBROUTINE dom_qe_zgr
222
223
224   SUBROUTINE dom_qe_sf_nxt( kt, Kbb, Kmm, Kaa, kcall )
225      !!----------------------------------------------------------------------
226      !!                ***  ROUTINE dom_qe_sf_nxt  ***
227      !!
228      !! ** Purpose :  - compute the after scale factors used in tra_zdf, dynnxt,
229      !!                 tranxt and dynspg routines
230      !!
231      !! ** Method  :  - z_star case:  Repartition of ssh INCREMENT proportionnaly to the level thickness.
232      !!
233      !! ** Action  :  - hdiv_lf    : restoring towards full baroclinic divergence in z_tilde case
234      !!               - tilde_e3t_a: after increment of vertical scale factor
235      !!                              in z_tilde case
236      !!               - e3(t/u/v)_a
237      !!
238      !! Reference  : Leclair, M., and Madec, G. 2011, Ocean Modelling.
239      !!----------------------------------------------------------------------
240      INTEGER, INTENT( in )           ::   kt             ! time step
241      INTEGER, INTENT( in )           ::   Kbb, Kmm, Kaa  ! time step
242      INTEGER, INTENT( in ), OPTIONAL ::   kcall          ! optional argument indicating call sequence
243      !
244      INTEGER                ::   ji, jj, jk            ! dummy loop indices
245      INTEGER , DIMENSION(3) ::   ijk_max, ijk_min      ! temporary integers
246      REAL(wp)               ::   z2dt, z_tmin, z_tmax  ! local scalars
247      LOGICAL                ::   ll_do_bclinic         ! local logical
248      REAL(wp), DIMENSION(jpi,jpj)     ::   zht, z_scale, zwu, zwv, zhdiv
249      !!----------------------------------------------------------------------
250      !
251      IF( ln_linssh )   RETURN      ! No calculation in linear free surface
252      !
253      IF( ln_timing )   CALL timing_start('dom_qe_sf_nxt')
254      !
255      IF( kt == nit000 ) THEN
256         IF(lwp) WRITE(numout,*)
257         IF(lwp) WRITE(numout,*) 'dom_qe_sf_nxt : compute after scale factors'
258         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~'
259      ENDIF
260
261      IF( PRESENT(kcall) ) THEN
262         IF( kcall == 2 ) THEN
263            CALL dom_qe_r3c( ssh(:,:,Kaa), r3t(:,:,Kaa), r3u(:,:,Kaa), r3v(:,:,Kaa), r3f(:,:) )
264         ELSE
265            CALL dom_qe_r3c( ssh(:,:,Kaa), r3t(:,:,Kaa), r3u(:,:,Kaa), r3v(:,:,Kaa) )
266         ENDIF
267      ENDIF
268
269      ! ******************************* !
270      ! After acale factors at t-points !
271      ! ******************************* !
272      !                                                ! --------------------------------------------- !
273      !                                                ! z_star coordinate and barotropic z-tilde part !
274      !                                                ! --------------------------------------------- !
275      !
276      !
277      ! *********************************** !
278      ! After scale factors at u- v- points !
279      ! *********************************** !
280      !
281      DO jk = 1, jpkm1
282         e3t(:,:,jk,Kaa) = e3t_0(:,:,jk) * ( 1._wp + r3t(:,:,Kaa) * tmask(:,:,jk) )
283         e3u(:,:,jk,Kaa) = e3u_0(:,:,jk) * ( 1._wp + r3u(:,:,Kaa) * umask(:,:,jk) )
284         e3v(:,:,jk,Kaa) = e3v_0(:,:,jk) * ( 1._wp + r3v(:,:,Kaa) * vmask(:,:,jk) )
285      END DO
286      !
287      ! *********************************** !
288      ! After depths at u- v points         !
289      ! *********************************** !
290      hu(:,:,Kaa) = hu_0(:,:) * ( 1._wp + r3u(:,:,Kaa) )
291      hv(:,:,Kaa) = hv_0(:,:) * ( 1._wp + r3v(:,:,Kaa) )
292      !                                        ! Inverse of the local depth
293      r1_hu(:,:,Kaa) = ssumask(:,:) / ( hu(:,:,Kaa) + 1._wp - ssumask(:,:) )
294      r1_hv(:,:,Kaa) = ssvmask(:,:) / ( hv(:,:,Kaa) + 1._wp - ssvmask(:,:) )
295      !
296      IF( ln_timing )   CALL timing_stop('dom_qe_sf_nxt')
297      !
298   END SUBROUTINE dom_qe_sf_nxt
299
300
301   SUBROUTINE dom_qe_sf_update( kt, Kbb, Kmm, Kaa )
302      !!----------------------------------------------------------------------
303      !!                ***  ROUTINE dom_qe_sf_update  ***
304      !!
305      !! ** Purpose :  for z tilde case: compute time filter and swap of scale factors
306      !!               compute all depths and related variables for next time step
307      !!               write outputs and restart file
308      !!
309      !! ** Method  :  - reconstruct scale factor at other grid points (interpolate)
310      !!               - recompute depths and water height fields
311      !!
312      !! ** Action  :  - Recompute:
313      !!                    e3(u/v)_b
314      !!                    e3w(:,:,:,Kmm)
315      !!                    e3(u/v)w_b
316      !!                    e3(u/v)w_n
317      !!                    gdept(:,:,:,Kmm), gdepw(:,:,:,Kmm)  and gde3w
318      !!                    h(u/v) and h(u/v)r
319      !!
320      !! Reference  : Leclair, M., and G. Madec, 2009, Ocean Modelling.
321      !!              Leclair, M., and G. Madec, 2011, Ocean Modelling.
322      !!----------------------------------------------------------------------
323      INTEGER, INTENT( in ) ::   kt              ! time step
324      INTEGER, INTENT( in ) ::   Kbb, Kmm, Kaa   ! time level indices
325      !
326      INTEGER  ::   ji, jj, jk   ! dummy loop indices
327      REAL(wp) ::   zcoef        ! local scalar
328      !!----------------------------------------------------------------------
329      !
330      IF( ln_linssh )   RETURN      ! No calculation in linear free surface
331      !
332      IF( ln_timing )   CALL timing_start('dom_qe_sf_update')
333      !
334      IF( kt == nit000 )   THEN
335         IF(lwp) WRITE(numout,*)
336         IF(lwp) WRITE(numout,*) 'dom_qe_sf_update : - interpolate scale factors and compute depths for next time step'
337         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~~~'
338      ENDIF
339      !
340      ! Compute all missing vertical scale factor and depths
341      ! ====================================================
342      ! Horizontal scale factor interpolations
343      ! --------------------------------------
344      ! - ML - e3u(:,:,:,Kbb) and e3v(:,:,:,Kbb) are already computed in dynnxt
345      ! - JC - hu(:,:,:,Kbb), hv(:,:,:,:,Kbb), hur_b, hvr_b also
346
347
348      ! Scale factor computation
349      DO jk = 1, jpk             ! Horizontal interpolation
350         e3f(:,:,jk)      =  e3f_0(:,:,jk) * ( 1._wp + r3f(:,:) * fmask(:,:,jk) )   ! Kmm time level
351         !                       ! Vertical interpolation
352         !                                   ! The ratio does not have to be masked at w-level
353         e3w (:,:,jk,Kmm) =  e3w_0(:,:,jk) * ( 1._wp + r3t(:,:,Kmm) )   ! Kmm time level
354         e3uw(:,:,jk,Kmm) = e3uw_0(:,:,jk) * ( 1._wp + r3u(:,:,Kmm) )
355         e3vw(:,:,jk,Kmm) = e3vw_0(:,:,jk) * ( 1._wp + r3v(:,:,Kmm) )
356         e3w (:,:,jk,Kbb) =  e3w_0(:,:,jk) * ( 1._wp + r3t(:,:,Kbb) )   ! Kbb time level
357         e3uw(:,:,jk,Kbb) = e3uw_0(:,:,jk) * ( 1._wp + r3u(:,:,Kbb) )
358         e3vw(:,:,jk,Kbb) = e3vw_0(:,:,jk) * ( 1._wp + r3v(:,:,Kbb) )
359      END DO
360
361
362      IF( ln_isf ) THEN          !** IceShelF cavities
363      !                             ! to be created depending of the new names in isf
364      !                             ! it should be something like that :  (with h_isf = thickness of iceshelf)
365      !                             !  in fact currently, h_isf(:,:) is called : risfdep(:,:)
366!!gm - depth idea 0  : just realize that mask is not needed ===>>>> with ISF, rescale all grid point position below ISF : no mask !
367         gdept(:,:,1,Kmm) = gdept_0(:,:,1) * ( 1._wp + r3t(:,:,Kmm) )
368         gdepw(:,:,1,Kmm) = 0._wp                            ! Initialized to zero one for all
369         gde3w(:,:,1)     = gdept(:,:,1,Kmm) - ssh(:,:,Kmm)  ! reference to a common level z=0 for hpg
370         DO jk = 2, jpk
371            gdept(:,:,jk,Kmm) = MIN( risfdep(:,:) , gdept_0(:,:,jk) )            &
372                              + MAX(   0._wp    , gdept_0(:,:,jk)-risfdep(:,:) ) * ( 1._wp + r3t(:,:,Kmm) )
373            gdepw(:,:,jk,Kmm) = MIN( risfdep(:,:) , gdepw_0(:,:,jk) )    &
374                              + MAX(   0._wp    , gdepw_0(:,:,jk)-risfdep(:,:) ) * ( 1._wp + r3t(:,:,Kmm) )
375            gde3w(:,:,jk)     = gdept(:,:,jk,Kmm) - ssh(:,:,Kmm)
376         END DO
377         !
378      ELSE                       !** No cavities   (all depth rescaled, even inside topography: no mask)
379         !
380!!gm idea 0 :   just realize that mask is not needed ===>>>> without ISF, rescale all grid point position : no mask !
381         DO jk = 1, jpk
382            gdept(:,:,jk,Kmm) = gdept_0(:,:,jk) * ( 1._wp + r3t(:,:,Kmm) )
383            gdepw(:,:,jk,Kmm) = gdepw_0(:,:,jk) * ( 1._wp + r3t(:,:,Kmm) )
384            gde3w(:,:,jk)     = gdept  (:,:,jk,Kmm)       - ssh(:,:,Kmm)
385         END DO
386         !
387      ENDIF
388
389      ! Local depth and Inverse of the local depth of the water
390      ! -------------------------------------------------------
391      !
392      ht(:,:) = ht_0(:,:) + ssh(:,:,Kmm)
393
394      ! write restart file
395      ! ==================
396      IF( lrst_oce  )   CALL dom_qe_rst( kt, Kbb, Kmm, 'WRITE' )
397      !
398      IF( ln_timing )   CALL timing_stop('dom_qe_sf_update')
399      !
400   END SUBROUTINE dom_qe_sf_update
401
402
403   SUBROUTINE dom_qe_interpol( pe3_in, pe3_out, pout )
404      !!---------------------------------------------------------------------
405      !!                  ***  ROUTINE dom_qe_interpol  ***
406      !!
407      !! ** Purpose :   interpolate scale factors from one grid point to another
408      !!
409      !! ** Method  :   e3_out = e3_0 + interpolation(e3_in - e3_0)
410      !!                - horizontal interpolation: grid cell surface averaging
411      !!                - vertical interpolation: simple averaging
412      !!----------------------------------------------------------------------
413      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in   ) ::  pe3_in    ! input e3 to be interpolated
414      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::  pe3_out   ! output interpolated e3
415      CHARACTER(LEN=*)                , INTENT(in   ) ::  pout      ! grid point of out scale factors
416      !                                                             !   =  'U', 'V', 'W, 'F', 'UW' or 'VW'
417      !
418      INTEGER ::   ji, jj, jk                                       ! dummy loop indices
419      REAL(wp) ::  zlnwd                                            ! =1./0. when ln_wd_il = T/F
420      !!----------------------------------------------------------------------
421      !
422      IF(ln_wd_il) THEN
423        zlnwd = 1.0_wp
424      ELSE
425        zlnwd = 0.0_wp
426      END IF
427      !
428      SELECT CASE ( pout )    !==  type of interpolation  ==!
429         !
430      CASE( 'U' )                   !* from T- to U-point : hor. surface weighted mean
431         DO_3D_10_10( 1, jpk )
432            pe3_out(ji,jj,jk) = 0.5_wp * (  umask(ji,jj,jk) * (1.0_wp - zlnwd) + zlnwd ) * r1_e1e2u(ji,jj)   &
433               &                       * (   e1e2t(ji  ,jj) * ( pe3_in(ji  ,jj,jk) - e3t_0(ji  ,jj,jk) )     &
434               &                           + e1e2t(ji+1,jj) * ( pe3_in(ji+1,jj,jk) - e3t_0(ji+1,jj,jk) ) )
435         END_3D
436         CALL lbc_lnk( 'domqe', pe3_out(:,:,:), 'U', 1._wp )
437         pe3_out(:,:,:) = pe3_out(:,:,:) + e3u_0(:,:,:)
438         !
439      CASE( 'V' )                   !* from T- to V-point : hor. surface weighted mean
440         DO_3D_10_10( 1, jpk )
441            pe3_out(ji,jj,jk) = 0.5_wp * ( vmask(ji,jj,jk)  * (1.0_wp - zlnwd) + zlnwd ) * r1_e1e2v(ji,jj)   &
442               &                       * (   e1e2t(ji,jj  ) * ( pe3_in(ji,jj  ,jk) - e3t_0(ji,jj  ,jk) )     &
443               &                           + e1e2t(ji,jj+1) * ( pe3_in(ji,jj+1,jk) - e3t_0(ji,jj+1,jk) ) )
444         END_3D
445         CALL lbc_lnk( 'domqe', pe3_out(:,:,:), 'V', 1._wp )
446         pe3_out(:,:,:) = pe3_out(:,:,:) + e3v_0(:,:,:)
447         !
448      CASE( 'F' )                   !* from U-point to F-point : hor. surface weighted mean
449         DO_3D_10_10( 1, jpk )
450            pe3_out(ji,jj,jk) = 0.5_wp * (  umask(ji,jj,jk) * umask(ji,jj+1,jk) * (1.0_wp - zlnwd) + zlnwd ) &
451               &                       *    r1_e1e2f(ji,jj)                                                  &
452               &                       * (   e1e2u(ji,jj  ) * ( pe3_in(ji,jj  ,jk) - e3u_0(ji,jj  ,jk) )     &
453               &                           + e1e2u(ji,jj+1) * ( pe3_in(ji,jj+1,jk) - e3u_0(ji,jj+1,jk) ) )
454         END_3D
455         CALL lbc_lnk( 'domqe', pe3_out(:,:,:), 'F', 1._wp )
456         pe3_out(:,:,:) = pe3_out(:,:,:) + e3f_0(:,:,:)
457         !
458      CASE( 'W' )                   !* from T- to W-point : vertical simple mean
459         !
460         !zlnwd = 1.0_wp
461         pe3_out(:,:,1) = e3w_0(:,:,1) + pe3_in(:,:,1) - e3t_0(:,:,1)
462         ! - ML - The use of mask in this formulea enables the special treatment of the last w-point without indirect adressing
463!!gm BUG? use here wmask in case of ISF ?  to be checked
464         DO jk = 2, jpk
465            pe3_out(:,:,jk) = e3w_0(:,:,jk) + ( 1.0_wp - 0.5_wp * ( tmask(:,:,jk) * (1.0_wp - zlnwd) + zlnwd ) )   &
466               &                            * ( pe3_in(:,:,jk-1) - e3t_0(:,:,jk-1) )                               &
467               &                            +            0.5_wp * ( tmask(:,:,jk) * (1.0_wp - zlnwd) + zlnwd )     &
468               &                            * ( pe3_in(:,:,jk  ) - e3t_0(:,:,jk  ) )
469         END DO
470         !
471      CASE( 'UW' )                  !* from U- to UW-point : vertical simple mean
472         !
473         !zlnwd = 1.0_wp
474         pe3_out(:,:,1) = e3uw_0(:,:,1) + pe3_in(:,:,1) - e3u_0(:,:,1)
475         ! - ML - The use of mask in this formaula enables the special treatment of the last w- point without indirect adressing
476!!gm BUG? use here wumask in case of ISF ?  to be checked
477         DO jk = 2, jpk
478            pe3_out(:,:,jk) = e3uw_0(:,:,jk) + ( 1.0_wp - 0.5_wp * ( umask(:,:,jk) * (1.0_wp - zlnwd) + zlnwd ) )  &
479               &                             * ( pe3_in(:,:,jk-1) - e3u_0(:,:,jk-1) )                              &
480               &                             +            0.5_wp * ( umask(:,:,jk) * (1.0_wp - zlnwd) + zlnwd )    &
481               &                             * ( pe3_in(:,:,jk  ) - e3u_0(:,:,jk  ) )
482         END DO
483         !
484      CASE( 'VW' )                  !* from V- to VW-point : vertical simple mean
485         !
486         !zlnwd = 1.0_wp
487         pe3_out(:,:,1) = e3vw_0(:,:,1) + pe3_in(:,:,1) - e3v_0(:,:,1)
488         ! - ML - The use of mask in this formaula enables the special treatment of the last w- point without indirect adressing
489!!gm BUG? use here wvmask in case of ISF ?  to be checked
490         DO jk = 2, jpk
491            pe3_out(:,:,jk) = e3vw_0(:,:,jk) + ( 1.0_wp - 0.5_wp * ( vmask(:,:,jk) * (1.0_wp - zlnwd) + zlnwd ) )  &
492               &                             * ( pe3_in(:,:,jk-1) - e3v_0(:,:,jk-1) )                              &
493               &                             +            0.5_wp * ( vmask(:,:,jk) * (1.0_wp - zlnwd) + zlnwd )    &
494               &                             * ( pe3_in(:,:,jk  ) - e3v_0(:,:,jk  ) )
495         END DO
496      END SELECT
497      !
498   END SUBROUTINE dom_qe_interpol
499
500
501   SUBROUTINE dom_qe_r3c( pssh, pr3t, pr3u, pr3v, pr3f )
502      !!---------------------------------------------------------------------
503      !!                   ***  ROUTINE r3c  ***
504      !!
505      !! ** Purpose :   compute the filtered ratio ssh/h_0 at t-,u-,v-,f-points
506      !!
507      !! ** Method  : - compute the ssh at u- and v-points (f-point optional)
508      !!                   Vector Form : surface weighted averaging
509      !!                   Flux   Form : simple           averaging
510      !!              - compute the ratio ssh/h_0 at t-,u-,v-pts, (f-pt optional)
511      !!----------------------------------------------------------------------
512      REAL(wp), DIMENSION(:,:)          , INTENT(in   )  ::   pssh               ! sea surface height   [m]
513      REAL(wp), DIMENSION(:,:)          , INTENT(  out)  ::   pr3t, pr3u, pr3v   ! ssh/h0 ratio at t-, u-, v-,points  [-]
514      REAL(wp), DIMENSION(:,:), OPTIONAL, INTENT(  out)  ::   pr3f               ! ssh/h0 ratio at f-point   [-]
515      !
516      INTEGER ::   ji, jj   ! dummy loop indices
517      !!----------------------------------------------------------------------
518      !
519      !
520      pr3t(:,:) = pssh(:,:) * r1_ht_0(:,:)   !==  ratio at t-point  ==!
521      !
522      !
523      !                                      !==  ratio at u-,v-point  ==!
524      !
525      IF( ln_dynadv_vec ) THEN                     !- Vector Form   (thickness weighted averaging)
526         DO_2D_11_11
527            pr3u(ji,jj) = 0.5_wp * (  e1e2t(ji  ,jj) * pssh(ji  ,jj)  &
528               &                    + e1e2t(ji+1,jj) * pssh(ji+1,jj)  ) * r1_hu_0(ji,jj) * r1_e1e2u(ji,jj)
529            pr3v(ji,jj) = 0.5_wp * (  e1e2t(ji,jj  ) * pssh(ji,jj  )  &
530               &                    + e1e2t(ji,jj+1) * pssh(ji,jj+1)  ) * r1_hv_0(ji,jj) * r1_e1e2v(ji,jj)
531         END_2D
532      ELSE                                         !- Flux Form   (simple averaging)
533         DO_2D_11_11
534            pr3u(ji,jj) = 0.5_wp * (  pssh(ji  ,jj) + pssh(ji+1,jj)  ) * r1_hu_0(ji,jj)
535            pr3v(ji,jj) = 0.5_wp * (  pssh(ji,jj  ) + pssh(ji,jj+1)  ) * r1_hv_0(ji,jj)
536         END_2D
537      ENDIF
538      !
539      IF( .NOT.PRESENT( pr3f ) ) THEN              !- lbc on ratio at u-, v-points only
540         CALL lbc_lnk_multi( 'dom_qe_r3c', pr3u, 'U', 1._wp, pr3v, 'V', 1._wp )
541         !
542         !
543      ELSE                                   !==  ratio at f-point  ==!
544         !
545         IF( ln_dynadv_vec )   THEN                !- Vector Form   (thickness weighted averaging)
546            DO_2D_01_01                               ! start from 1 since lbc_lnk('F') doesn't update the 1st row/line
547               pr3f(ji,jj) = 0.25_wp * (  e1e2t(ji  ,jj  ) * pssh(ji  ,jj  )  &
548                  &                     + e1e2t(ji+1,jj  ) * pssh(ji+1,jj  )  &
549                  &                     + e1e2t(ji  ,jj+1) * pssh(ji  ,jj+1)  &
550                  &                     + e1e2t(ji+1,jj+1) * pssh(ji+1,jj+1)  ) * r1_hf_0(ji,jj) * r1_e1e2f(ji,jj)
551            END_2D
552         ELSE                                      !- Flux Form   (simple averaging)
553            DO_2D_01_01                               ! start from 1 since lbc_lnk('F') doesn't update the 1st row/line
554               pr3f(ji,jj) = 0.25_wp * (  pssh(ji  ,jj  ) + pssh(ji+1,jj  )  &
555                  &                     + pssh(ji  ,jj+1) + pssh(ji+1,jj+1)  ) * r1_hf_0(ji,jj)
556            END_2D
557         ENDIF
558         !                                                 ! lbc on ratio at u-,v-,f-points
559         CALL lbc_lnk_multi( 'dom_qe_r3c', pr3u, 'U', 1._wp, pr3v, 'V', 1._wp, pr3f, 'F', 1._wp )
560         !
561      ENDIF
562      !
563   END SUBROUTINE dom_qe_r3c
564
565
566   SUBROUTINE dom_qe_rst( kt, Kbb, Kmm, cdrw )
567      !!---------------------------------------------------------------------
568      !!                   ***  ROUTINE dom_qe_rst  ***
569      !!
570      !! ** Purpose :   Read or write VVL file in restart file
571      !!
572      !! ** Method  :   use of IOM library
573      !!                if the restart does not contain vertical scale factors,
574      !!                they are set to the _0 values
575      !!                if the restart does not contain vertical scale factors increments (z_tilde),
576      !!                they are set to 0.
577      !!----------------------------------------------------------------------
578      INTEGER         , INTENT(in) ::   kt        ! ocean time-step
579      INTEGER         , INTENT(in) ::   Kbb, Kmm  ! ocean time level indices
580      CHARACTER(len=*), INTENT(in) ::   cdrw      ! "READ"/"WRITE" flag
581      !
582      INTEGER ::   ji, jj, jk
583      INTEGER ::   id1, id2     ! local integers
584      !!----------------------------------------------------------------------
585      !
586      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise
587         !                                   ! ===============
588         IF( ln_rstart ) THEN                   !* Read the restart file
589            CALL rst_read_open                  !  open the restart file if necessary
590            CALL iom_get( numror, jpdom_autoglo, 'sshn'   , ssh(:,:,Kmm), ldxios = lrxios    )
591            !
592            id1 = iom_varid( numror, 'e3t_b', ldstop = .FALSE. )
593            id2 = iom_varid( numror, 'e3t_n', ldstop = .FALSE. )
594            !
595            !                             ! --------- !
596            !                             ! all cases !
597            !                             ! --------- !
598            !
599            IF( MIN( id1, id2 ) > 0 ) THEN       ! all required arrays exist
600               CALL iom_get( numror, jpdom_autoglo, 'e3t_b', e3t(:,:,:,Kbb), ldxios = lrxios )
601               CALL iom_get( numror, jpdom_autoglo, 'e3t_n', e3t(:,:,:,Kmm), ldxios = lrxios )
602               ! needed to restart if land processor not computed
603               IF(lwp) write(numout,*) 'dom_qe_rst : e3t(:,:,:,Kbb) and e3t(:,:,:,Kmm) found in restart files'
604               WHERE ( tmask(:,:,:) == 0.0_wp )
605                  e3t(:,:,:,Kmm) = e3t_0(:,:,:)
606                  e3t(:,:,:,Kbb) = e3t_0(:,:,:)
607               END WHERE
608               IF( neuler == 0 ) THEN
609                  e3t(:,:,:,Kbb) = e3t(:,:,:,Kmm)
610               ENDIF
611            ELSE IF( id1 > 0 ) THEN
612               IF(lwp) write(numout,*) 'dom_qe_rst WARNING : e3t(:,:,:,Kmm) not found in restart files'
613               IF(lwp) write(numout,*) 'e3t_n set equal to e3t_b.'
614               IF(lwp) write(numout,*) 'neuler is forced to 0'
615               CALL iom_get( numror, jpdom_autoglo, 'e3t_b', e3t(:,:,:,Kbb), ldxios = lrxios )
616               e3t(:,:,:,Kmm) = e3t(:,:,:,Kbb)
617               neuler = 0
618            ELSE IF( id2 > 0 ) THEN
619               IF(lwp) write(numout,*) 'dom_qe_rst WARNING : e3t(:,:,:,Kbb) not found in restart files'
620               IF(lwp) write(numout,*) 'e3t_b set equal to e3t_n.'
621               IF(lwp) write(numout,*) 'neuler is forced to 0'
622               CALL iom_get( numror, jpdom_autoglo, 'e3t_n', e3t(:,:,:,Kmm), ldxios = lrxios )
623               e3t(:,:,:,Kbb) = e3t(:,:,:,Kmm)
624               neuler = 0
625            ELSE
626               IF(lwp) write(numout,*) 'dom_qe_rst WARNING : e3t(:,:,:,Kmm) not found in restart file'
627               IF(lwp) write(numout,*) 'Compute scale factor from sshn'
628               IF(lwp) write(numout,*) 'neuler is forced to 0'
629               DO jk = 1, jpk
630                  e3t(:,:,jk,Kmm) =  e3t_0(:,:,jk) * ( ht_0(:,:) + ssh(:,:,Kmm) ) &
631                      &                          / ( ht_0(:,:) + 1._wp - ssmask(:,:) ) * tmask(:,:,jk)   &
632                      &          + e3t_0(:,:,jk)                               * (1._wp -tmask(:,:,jk))
633               END DO
634               e3t(:,:,:,Kbb) = e3t(:,:,:,Kmm)
635               neuler = 0
636            ENDIF
637            !
638         ELSE                                   !* Initialize at "rest"
639            !
640            IF( ll_wd ) THEN   ! MJB ll_wd edits start here - these are essential
641               !
642               IF( cn_cfg == 'wad' ) THEN
643                  ! Wetting and drying test case
644                  CALL usr_def_istate( gdept(:,:,:,Kbb), tmask, ts(:,:,:,:,Kbb), uu(:,:,:,Kbb), vv(:,:,:,Kbb), ssh(:,:,Kbb)  )
645                  ts  (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb)       ! set now values from to before ones
646                  ssh (:,:,Kmm)     = ssh(:,:,Kbb)
647                  uu   (:,:,:,Kmm)   = uu  (:,:,:,Kbb)
648                  vv   (:,:,:,Kmm)   = vv  (:,:,:,Kbb)
649               ELSE
650                  ! if not test case
651                  ssh(:,:,Kmm) = -ssh_ref
652                  ssh(:,:,Kbb) = -ssh_ref
653
654                  DO_2D_11_11
655                     IF( ht_0(ji,jj)-ssh_ref <  rn_wdmin1 ) THEN ! if total depth is less than min depth
656                        ssh(ji,jj,Kbb) = rn_wdmin1 - (ht_0(ji,jj) )
657                        ssh(ji,jj,Kmm) = rn_wdmin1 - (ht_0(ji,jj) )
658                     ENDIF
659                  END_2D
660               ENDIF !If test case else
661
662               ! Adjust vertical metrics for all wad
663               DO jk = 1, jpk
664                  e3t(:,:,jk,Kmm) = e3t_0(:,:,jk) * ( 1._wp + r3t(:,:,Kmm) * tmask(:,:,jk) )
665               END DO
666               e3t(:,:,:,Kbb) = e3t(:,:,:,Kmm)
667
668               DO ji = 1, jpi
669                  DO jj = 1, jpj
670                     IF ( ht_0(ji,jj) .LE. 0.0 .AND. NINT( ssmask(ji,jj) ) .EQ. 1) THEN
671                       CALL ctl_stop( 'dom_qe_rst: ht_0 must be positive at potentially wet points' )
672                     ENDIF
673                  END DO
674               END DO
675               !
676            ELSE
677               !
678               ! Just to read set ssh in fact, called latter once vertical grid
679               ! is set up:
680!               CALL usr_def_istate( gdept_0, tmask, ts(:,:,:,:,Kbb), uu(:,:,:,Kbb), vv(:,:,:,Kbb), ssh(:,:,Kbb)  )
681!               !
682!               DO jk=1,jpk
683!                  e3t(:,:,jk,Kbb) =  e3t_0(:,:,jk) * ( ht_0(:,:) + ssh(:,:,Kbb) ) &
684!                     &            / ( ht_0(:,:) + 1._wp -ssmask(:,:) ) * tmask(:,:,jk)
685!               END DO
686!               e3t(:,:,:,Kmm) = e3t(:,:,:,Kbb)
687                ssh(:,:,Kmm)=0._wp
688                e3t(:,:,:,Kmm)=e3t_0(:,:,:)
689                e3t(:,:,:,Kbb)=e3t_0(:,:,:)
690               !
691            ENDIF           ! end of ll_wd edits
692            !
693         ENDIF
694         !
695      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file
696         !                                   ! ===================
697         IF(lwp) WRITE(numout,*) '---- dom_qe_rst ----'
698         IF( lwxios ) CALL iom_swap(      cwxios_context          )
699         !                                           ! --------- !
700         !                                           ! all cases !
701         !                                           ! --------- !
702         CALL iom_rstput( kt, nitrst, numrow, 'e3t_b', e3t(:,:,:,Kbb), ldxios = lwxios )
703         CALL iom_rstput( kt, nitrst, numrow, 'e3t_n', e3t(:,:,:,Kmm), ldxios = lwxios )
704         !
705         IF( lwxios ) CALL iom_swap(      cxios_context          )
706      ENDIF
707      !
708   END SUBROUTINE dom_qe_rst
709
710
711   SUBROUTINE dom_qe_ctl
712      !!---------------------------------------------------------------------
713      !!                  ***  ROUTINE dom_qe_ctl  ***
714      !!
715      !! ** Purpose :   Control the consistency between namelist options
716      !!                for vertical coordinate
717      !!----------------------------------------------------------------------
718      INTEGER ::   ioptio, ios
719      !!
720      NAMELIST/nam_vvl/ ln_vvl_zstar, ln_vvl_ztilde, ln_vvl_layer, ln_vvl_ztilde_as_zstar, &
721         &              ln_vvl_zstar_at_eqtor      , rn_ahe3     , rn_rst_e3t            , &
722         &              rn_lf_cutoff               , rn_zdef_max , ln_vvl_dbg                ! not yet implemented: ln_vvl_kepe
723      !!----------------------------------------------------------------------
724      !
725      READ  ( numnam_ref, nam_vvl, IOSTAT = ios, ERR = 901)
726901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nam_vvl in reference namelist' )
727      READ  ( numnam_cfg, nam_vvl, IOSTAT = ios, ERR = 902 )
728902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nam_vvl in configuration namelist' )
729      IF(lwm) WRITE ( numond, nam_vvl )
730      !
731      IF(lwp) THEN                    ! Namelist print
732         WRITE(numout,*)
733         WRITE(numout,*) 'dom_qe_ctl : choice/control of the variable vertical coordinate'
734         WRITE(numout,*) '~~~~~~~~~~~'
735         WRITE(numout,*) '   Namelist nam_vvl : chose a vertical coordinate'
736         WRITE(numout,*) '      zstar                      ln_vvl_zstar   = ', ln_vvl_zstar
737         WRITE(numout,*) '      ztilde                     ln_vvl_ztilde  = ', ln_vvl_ztilde
738         WRITE(numout,*) '      layer                      ln_vvl_layer   = ', ln_vvl_layer
739         WRITE(numout,*) '      ztilde as zstar   ln_vvl_ztilde_as_zstar  = ', ln_vvl_ztilde_as_zstar
740         WRITE(numout,*) '      ztilde near the equator    ln_vvl_zstar_at_eqtor  = ', ln_vvl_zstar_at_eqtor
741         WRITE(numout,*) '      !'
742         WRITE(numout,*) '      thickness diffusion coefficient                      rn_ahe3      = ', rn_ahe3
743         WRITE(numout,*) '      maximum e3t deformation fractional change            rn_zdef_max  = ', rn_zdef_max
744         IF( ln_vvl_ztilde_as_zstar ) THEN
745            WRITE(numout,*) '      ztilde running in zstar emulation mode (ln_vvl_ztilde_as_zstar=T) '
746            WRITE(numout,*) '         ignoring namelist timescale parameters and using:'
747            WRITE(numout,*) '            hard-wired : z-tilde to zstar restoration timescale (days)'
748            WRITE(numout,*) '                         rn_rst_e3t     = 0.e0'
749            WRITE(numout,*) '            hard-wired : z-tilde cutoff frequency of low-pass filter (days)'
750            WRITE(numout,*) '                         rn_lf_cutoff   = 1.0/rdt'
751         ELSE
752            WRITE(numout,*) '      z-tilde to zstar restoration timescale (days)        rn_rst_e3t   = ', rn_rst_e3t
753            WRITE(numout,*) '      z-tilde cutoff frequency of low-pass filter (days)   rn_lf_cutoff = ', rn_lf_cutoff
754         ENDIF
755         WRITE(numout,*) '         debug prints flag                                 ln_vvl_dbg   = ', ln_vvl_dbg
756      ENDIF
757      !
758      ioptio = 0                      ! Parameter control
759      IF( ln_vvl_ztilde_as_zstar )   ln_vvl_ztilde = .true.
760      IF( ln_vvl_zstar           )   ioptio = ioptio + 1
761      IF( ln_vvl_ztilde          )   ioptio = ioptio + 1
762      IF( ln_vvl_layer           )   ioptio = ioptio + 1
763      !
764      IF( ioptio /= 1 )   CALL ctl_stop( 'Choose ONE vertical coordinate in namelist nam_vvl' )
765      !
766      IF(lwp) THEN                   ! Print the choice
767         WRITE(numout,*)
768         IF( ln_vvl_zstar           ) WRITE(numout,*) '      ==>>>   zstar vertical coordinate is used'
769         IF( ln_vvl_ztilde          ) WRITE(numout,*) '      ==>>>   ztilde vertical coordinate is used'
770         IF( ln_vvl_layer           ) WRITE(numout,*) '      ==>>>   layer vertical coordinate is used'
771         IF( ln_vvl_ztilde_as_zstar ) WRITE(numout,*) '      ==>>>   to emulate a zstar coordinate'
772      ENDIF
773      !
774#if defined key_agrif
775      IF( (.NOT.Agrif_Root()).AND.(.NOT.ln_vvl_zstar) )   CALL ctl_stop( 'AGRIF is implemented with zstar coordinate only' )
776#endif
777      !
778   END SUBROUTINE dom_qe_ctl
779
780   !!======================================================================
781END MODULE domqe
Note: See TracBrowser for help on using the repository browser.