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/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf.F90 @ 8102

Last change on this file since 8102 was 8102, checked in by davestorkey, 7 years ago

NEMO 3.6_stable: tracer trends diagnostics. See ticket #1877 for more details.

  1. Correct bugs in calculation of total trends and trends due to vertical diffusion.
  2. Output component trends every second timestep so that sum of component trends plus Asselin filter trend equals total trend.
  3. Layer-integrated versions of trends (as per CMIP6 definition) available in field_def.xml.
  • Property svn:keywords set to Id
File size: 8.6 KB
RevLine 
[458]1MODULE trazdf
2   !!==============================================================================
3   !!                 ***  MODULE  trazdf  ***
4   !! Ocean active tracers:  vertical component of the tracer mixing trend
5   !!==============================================================================
[2528]6   !! History :  1.0  ! 2005-11  (G. Madec)  Original code
7   !!            3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
[458]8   !!----------------------------------------------------------------------
[503]9
10   !!----------------------------------------------------------------------
[458]11   !!   tra_zdf      : Update the tracer trend with the vertical diffusion
[2528]12   !!   tra_zdf_init : initialisation of the computation
[458]13   !!----------------------------------------------------------------------
14   USE oce             ! ocean dynamics and tracers variables
15   USE dom_oce         ! ocean space and time domain variables
[2715]16   USE domvvl          ! variable volume
17   USE phycst          ! physical constant
[458]18   USE zdf_oce         ! ocean vertical physics variables
[888]19   USE sbc_oce         ! surface boundary condition: ocean
20   USE dynspg_oce
[458]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
[4990]24   USE trd_oce         ! trends: ocean variables
25   USE trdtra          ! trends manager: tracers
26   !
[458]27   USE in_out_manager  ! I/O manager
28   USE prtctl          ! Print control
[592]29   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
[2715]30   USE lib_mpp         ! MPP library
[3294]31   USE wrk_nemo        ! Memory allocation
32   USE timing          ! Timing
[592]33
[458]34   IMPLICIT NONE
35   PRIVATE
36
[2715]37   PUBLIC   tra_zdf        ! routine called by step.F90
38   PUBLIC   tra_zdf_init   ! routine called by nemogcm.F90
[458]39
[2715]40   INTEGER ::   nzdf = 0   ! type vertical diffusion algorithm used (defined from ln_zdf...  namlist logicals)
[458]41
42   !! * Substitutions
43#  include "domzgr_substitute.h90"
44#  include "zdfddm_substitute.h90"
45#  include "vectopt_loop_substitute.h90"
46   !!----------------------------------------------------------------------
[4990]47   !! NEMO/OPA 3.7 , NEMO Consortium (2014)
[888]48   !! $Id$
[2715]49   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[458]50   !!----------------------------------------------------------------------
[2715]51CONTAINS
[458]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
[2528]60      !!
[458]61      INTEGER  ::   jk                   ! Dummy loop indices
[3294]62      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrdt, ztrds   ! 3D workspace
[458]63      !!---------------------------------------------------------------------
[3294]64      !
65      IF( nn_timing == 1 )  CALL timing_start('tra_zdf')
66      !
[458]67      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000
[2715]68         r2dtra(:) =  rdttra(:)                          ! = rdtra (restarting with Euler time stepping)
[458]69      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1
[2715]70         r2dtra(:) = 2. * rdttra(:)                      ! = 2 rdttra (leapfrog)
[458]71      ENDIF
72
[2528]73      IF( l_trdtra )   THEN                    !* Save ta and sa trends
[3294]74         CALL wrk_alloc( jpi, jpj, jpk, ztrdt, ztrds )
75         ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
76         ztrds(:,:,:) = tsa(:,:,:,jp_sal)
[458]77      ENDIF
78
79      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend
[3294]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
[458]82      CASE ( -1 )                                       ! esopa: test all possibility with control print
[3294]83         CALL tra_zdf_exp( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb, tsa, jpts )
[2528]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' )
[3294]86         CALL tra_zdf_imp( kt, nit000, 'TRA', r2dtra,            tsb, tsa, jpts ) 
[2528]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' )
[458]89      END SELECT
[5385]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
[458]94
[1110]95      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics
[8102]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
[4990]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 )
[3294]114         CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds )
[1110]115      ENDIF
116
117      !                                          ! print mean trends (used for debugging)
[2528]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' )
[2715]120      !
[3294]121      IF( nn_timing == 1 )  CALL timing_stop('tra_zdf')
122      !
[458]123   END SUBROUTINE tra_zdf
124
125
[2528]126   SUBROUTINE tra_zdf_init
[458]127      !!----------------------------------------------------------------------
[2528]128      !!                 ***  ROUTINE tra_zdf_init  ***
[458]129      !!
130      !! ** Purpose :   Choose the vertical mixing scheme
131      !!
[789]132      !! ** Method  :   Set nzdf from ln_zdfexp
[458]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
[2528]139      USE zdfgls
[458]140      USE zdfkpp
141      !!----------------------------------------------------------------------
142
143      ! Choice from ln_zdfexp already read in namelist in zdfini module
[2528]144      IF( ln_zdfexp ) THEN   ;   nzdf = 0           ! use explicit scheme
145      ELSE                   ;   nzdf = 1           ! use implicit scheme
[458]146      ENDIF
147
148      ! Force implicit schemes
[2528]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.' )
[458]154
155      ! Test: esopa
156      IF( lk_esopa )    nzdf = -1                      ! All schemes used
157
158      IF(lwp) THEN
159         WRITE(numout,*)
[2528]160         WRITE(numout,*) 'tra_zdf_init : vertical tracer physics scheme'
[458]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      ENDIF
[2528]166      !
167   END SUBROUTINE tra_zdf_init
[458]168
169   !!==============================================================================
170END MODULE trazdf
Note: See TracBrowser for help on using the repository browser.