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.
trazdf.F90 in branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf.F90 @ 11101

Last change on this file since 11101 was 11101, checked in by frrh, 5 years ago

Merge changes from Met Office GMED ticket 450 to reduce unnecessary
text output from NEMO.
This output, which is typically not switchable, is rarely of interest
in normal (non-debugging) runs and simply redunantley consumes extra
file space.
Further, the presence of this text output has been shown to
significantly degrade performance of models which are run during
Met Office HPC RAID (disk) checks.
The new code introduces switches which are configurable via the
changes made in the associated Met Office MOCI ticket 399.

File size: 8.6 KB
Line 
1MODULE trazdf
2   !!==============================================================================
3   !!                 ***  MODULE  trazdf  ***
4   !! Ocean active tracers:  vertical component of the tracer mixing trend
5   !!==============================================================================
6   !! History :  1.0  ! 2005-11  (G. Madec)  Original code
7   !!            3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   tra_zdf      : Update the tracer trend with the vertical diffusion
12   !!   tra_zdf_init : initialisation of the computation
13   !!----------------------------------------------------------------------
14   USE oce             ! ocean dynamics and tracers variables
15   USE dom_oce         ! ocean space and time domain variables
16   USE domvvl          ! variable volume
17   USE phycst          ! physical constant
18   USE zdf_oce         ! ocean vertical physics variables
19   USE sbc_oce         ! surface boundary condition: ocean
20   USE dynspg_oce
21   USE trazdf_exp      ! vertical diffusion: explicit (tra_zdf_exp     routine)
22   USE trazdf_imp      ! vertical diffusion: implicit (tra_zdf_imp     routine)
23   USE ldftra_oce      ! ocean active tracers: lateral physics
24   USE trd_oce         ! trends: ocean variables
25   USE trdtra          ! trends manager: tracers
26   !
27   USE in_out_manager  ! I/O manager
28   USE prtctl          ! Print control
29   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
30   USE lib_mpp         ! MPP library
31   USE wrk_nemo        ! Memory allocation
32   USE timing          ! Timing
33
34   IMPLICIT NONE
35   PRIVATE
36
37   PUBLIC   tra_zdf        ! routine called by step.F90
38   PUBLIC   tra_zdf_init   ! routine called by nemogcm.F90
39
40   INTEGER ::   nzdf = 0   ! type vertical diffusion algorithm used (defined from ln_zdf...  namlist logicals)
41
42   !! * Substitutions
43#  include "domzgr_substitute.h90"
44#  include "zdfddm_substitute.h90"
45#  include "vectopt_loop_substitute.h90"
46   !!----------------------------------------------------------------------
47   !! NEMO/OPA 3.7 , NEMO Consortium (2014)
48   !! $Id$
49   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
50   !!----------------------------------------------------------------------
51CONTAINS
52
53   SUBROUTINE tra_zdf( kt )
54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE tra_zdf  ***
56      !!
57      !! ** Purpose :   compute the vertical ocean tracer physics.
58      !!---------------------------------------------------------------------
59      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
60      !!
61      INTEGER  ::   jk                   ! Dummy loop indices
62      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrdt, ztrds   ! 3D workspace
63      !!---------------------------------------------------------------------
64      !
65      IF( nn_timing == 1 )  CALL timing_start('tra_zdf')
66      !
67      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000
68         r2dtra(:) =  rdttra(:)                          ! = rdtra (restarting with Euler time stepping)
69      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1
70         r2dtra(:) = 2. * rdttra(:)                      ! = 2 rdttra (leapfrog)
71      ENDIF
72
73      IF( l_trdtra )   THEN                    !* Save ta and sa trends
74         CALL wrk_alloc( jpi, jpj, jpk, ztrdt, ztrds )
75         ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
76         ztrds(:,:,:) = tsa(:,:,:,jp_sal)
77      ENDIF
78
79      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend
80      CASE ( 0 )    ;    CALL tra_zdf_exp( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb, tsa, jpts )  !   explicit scheme
81      CASE ( 1 )    ;    CALL tra_zdf_imp( kt, nit000, 'TRA', r2dtra,            tsb, tsa, jpts )  !   implicit scheme
82      CASE ( -1 )                                       ! esopa: test all possibility with control print
83         CALL tra_zdf_exp( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb, tsa, jpts )
84         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf0 - Ta: ', mask1=tmask,               &
85         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
86         CALL tra_zdf_imp( kt, nit000, 'TRA', r2dtra,            tsb, tsa, jpts ) 
87         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf1 - Ta: ', mask1=tmask,               &
88         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
89      END SELECT
90      ! DRAKKAR SSS control {
91      ! JMM avoid negative salinities near river outlet ! Ugly fix
92      ! JMM : restore negative salinities to small salinities:
93      WHERE ( tsa(:,:,:,jp_sal) < 0._wp )   tsa(:,:,:,jp_sal) = 0.1_wp
94
95      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics
96         ! G Nurser 23 Mar 2017. Recalculate trend as Delta(e3t*T)/e3tn.
97         IF( lk_vvl ) THEN
98            DO jk = 1, jpkm1
99               ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem)*fse3t_a(:,:,jk) - tsb(:,:,jk,jp_tem)*fse3t_b(:,:,jk) ) &
100                    & / (fse3t_n(:,:,jk)*r2dtra(jk)) ) - ztrdt(:,:,jk)
101               ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal)*fse3t_a(:,:,jk) - tsb(:,:,jk,jp_sal)*fse3t_b(:,:,jk) ) &
102                    & / (fse3t_n(:,:,jk)*r2dtra(jk)) ) - ztrds(:,:,jk)
103            END DO
104         ELSE
105            DO jk = 1, jpkm1
106               ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / r2dtra(jk) ) - ztrdt(:,:,jk)
107               ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / r2dtra(jk) ) - ztrds(:,:,jk)
108            END DO
109         END IF
110         CALL lbc_lnk( ztrdt, 'T', 1. )
111         CALL lbc_lnk( ztrds, 'T', 1. )
112         CALL trd_tra( kt, 'TRA', jp_tem, jptra_zdf, ztrdt )
113         CALL trd_tra( kt, 'TRA', jp_sal, jptra_zdf, ztrds )
114         CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds )
115      ENDIF
116
117      !                                          ! print mean trends (used for debugging)
118      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf  - Ta: ', mask1=tmask,               &
119         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
120      !
121      IF( nn_timing == 1 )  CALL timing_stop('tra_zdf')
122      !
123   END SUBROUTINE tra_zdf
124
125
126   SUBROUTINE tra_zdf_init
127      !!----------------------------------------------------------------------
128      !!                 ***  ROUTINE tra_zdf_init  ***
129      !!
130      !! ** Purpose :   Choose the vertical mixing scheme
131      !!
132      !! ** Method  :   Set nzdf from ln_zdfexp
133      !!      nzdf = 0   explicit (time-splitting) scheme (ln_zdfexp=T)
134      !!           = 1   implicit (euler backward) scheme (ln_zdfexp=F)
135      !!      NB: rotation of lateral mixing operator or TKE or KPP scheme,
136      !!      the implicit scheme is required.
137      !!----------------------------------------------------------------------
138      USE zdftke
139      USE zdfgls
140      USE zdfkpp
141      !!----------------------------------------------------------------------
142
143      ! Choice from ln_zdfexp already read in namelist in zdfini module
144      IF( ln_zdfexp ) THEN   ;   nzdf = 0           ! use explicit scheme
145      ELSE                   ;   nzdf = 1           ! use implicit scheme
146      ENDIF
147
148      ! Force implicit schemes
149      IF( lk_zdftke .OR. lk_zdfgls .OR. lk_zdfkpp )   nzdf = 1      ! TKE, GLS or KPP physics
150      IF( ln_traldf_iso                           )   nzdf = 1      ! iso-neutral lateral physics
151      IF( ln_traldf_hor .AND. ln_sco              )   nzdf = 1      ! horizontal lateral physics in s-coordinate
152      IF( ln_zdfexp .AND. nzdf == 1 )   CALL ctl_stop( 'tra_zdf : If using the rotation of lateral mixing operator',   &
153            &                         ' TKE or KPP scheme, the implicit scheme is required, set ln_zdfexp = .false.' )
154
155      ! Test: esopa
156      IF( lk_esopa )    nzdf = -1                      ! All schemes used
157
158      IF(lwp) THEN
159         WRITE(numout,*)
160         WRITE(numout,*) 'tra_zdf_init : vertical tracer physics scheme'
161         WRITE(numout,*) '~~~~~~~~~~~'
162         IF( nzdf == -1 )   WRITE(numout,*) '              ESOPA test All scheme used'
163         IF( nzdf ==  0 )   WRITE(numout,*) '              Explicit time-splitting scheme'
164         IF( nzdf ==  1 )   WRITE(numout,*) '              Implicit (euler backward) scheme'
165         IF(lflush) CALL flush(numout)
166      ENDIF
167      !
168   END SUBROUTINE tra_zdf_init
169
170   !!==============================================================================
171END MODULE trazdf
Note: See TracBrowser for help on using the repository browser.