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

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf.F90 @ 5870

Last change on this file since 5870 was 5870, checked in by acc, 8 years ago

Branch 2015/dev_r5803_NOC_WAD. Merge in trunk changes from 5803 to 5869 in preparation for merge. Also tidied and reorganised some wetting and drying code. Renamed wadlmt.F90 to wetdry.F90. Wetting drying code changes restricted to domzgr.F90, domvvl.F90 nemogcm.F90 sshwzv.F90, dynspg_ts.F90, wetdry.F90 and dynhpg.F90. Code passes full SETTE tests with ln_wd=.false.. Still awaiting test case for checking with ln_wd=.false.

  • Property svn:keywords set to Id
File size: 7.3 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   !
22   USE ldftra          ! lateral diffusion: eddy diffusivity
23   USE ldfslp          ! lateral diffusion: iso-neutral slope
24   USE trazdf_exp      ! vertical diffusion: explicit (tra_zdf_exp     routine)
25   USE trazdf_imp      ! vertical diffusion: implicit (tra_zdf_imp     routine)
26   !
27   USE trd_oce         ! trends: ocean variables
28   USE trdtra          ! trends manager: tracers
29   !
30   USE in_out_manager  ! I/O manager
31   USE prtctl          ! Print control
32   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
33   USE lib_mpp         ! MPP library
34   USE wrk_nemo        ! Memory allocation
35   USE timing          ! Timing
36
37   IMPLICIT NONE
38   PRIVATE
39
40   PUBLIC   tra_zdf        ! routine called by step.F90
41   PUBLIC   tra_zdf_init   ! routine called by nemogcm.F90
42
43   INTEGER ::   nzdf = 0   ! type vertical diffusion algorithm used (defined from ln_zdf...  namlist logicals)
44
45   !! * Substitutions
46#  include "domzgr_substitute.h90"
47#  include "zdfddm_substitute.h90"
48#  include "vectopt_loop_substitute.h90"
49   !!----------------------------------------------------------------------
50   !! NEMO/OPA 3.7 , NEMO Consortium (2015)
51   !! $Id$
52   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
53   !!----------------------------------------------------------------------
54CONTAINS
55
56   SUBROUTINE tra_zdf( kt )
57      !!----------------------------------------------------------------------
58      !!                  ***  ROUTINE tra_zdf  ***
59      !!
60      !! ** Purpose :   compute the vertical ocean tracer physics.
61      !!---------------------------------------------------------------------
62      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
63      !!
64      INTEGER  ::   jk                   ! Dummy loop indices
65      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrdt, ztrds   ! 3D workspace
66      !!---------------------------------------------------------------------
67      !
68      IF( nn_timing == 1 )  CALL timing_start('tra_zdf')
69      !
70      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000
71         r2dtra(:) =  rdttra(:)                          ! = rdtra (restarting with Euler time stepping)
72      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1
73         r2dtra(:) = 2. * rdttra(:)                      ! = 2 rdttra (leapfrog)
74      ENDIF
75
76      IF( l_trdtra )   THEN                    !* Save ta and sa trends
77         CALL wrk_alloc( jpi, jpj, jpk, ztrdt, ztrds )
78         ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
79         ztrds(:,:,:) = tsa(:,:,:,jp_sal)
80      ENDIF
81
82      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend
83      CASE ( 0 )    ;    CALL tra_zdf_exp( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb, tsa, jpts )  !   explicit scheme
84      CASE ( 1 )    ;    CALL tra_zdf_imp( kt, nit000, 'TRA', r2dtra,            tsb, tsa, jpts )  !   implicit scheme
85      END SELECT
86!!gm WHY here !   and I don't like that !
87      ! DRAKKAR SSS control {
88      ! JMM avoid negative salinities near river outlet ! Ugly fix
89      ! JMM : restore negative salinities to small salinities:
90      WHERE ( tsa(:,:,:,jp_sal) < 0._wp )   tsa(:,:,:,jp_sal) = 0.1_wp
91!!gm
92
93      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics
94         DO jk = 1, jpkm1
95            ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / r2dtra(jk) ) - ztrdt(:,:,jk)
96            ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / r2dtra(jk) ) - ztrds(:,:,jk)
97         END DO
98!!gm this should be moved in trdtra.F90 and done on all trends
99         CALL lbc_lnk( ztrdt, 'T', 1. )
100         CALL lbc_lnk( ztrds, 'T', 1. )
101!!gm
102         CALL trd_tra( kt, 'TRA', jp_tem, jptra_zdf, ztrdt )
103         CALL trd_tra( kt, 'TRA', jp_sal, jptra_zdf, ztrds )
104         CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds )
105      ENDIF
106
107      !                                          ! print mean trends (used for debugging)
108      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf  - Ta: ', mask1=tmask,               &
109         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
110      !
111      IF( nn_timing == 1 )  CALL timing_stop('tra_zdf')
112      !
113   END SUBROUTINE tra_zdf
114
115
116   SUBROUTINE tra_zdf_init
117      !!----------------------------------------------------------------------
118      !!                 ***  ROUTINE tra_zdf_init  ***
119      !!
120      !! ** Purpose :   Choose the vertical mixing scheme
121      !!
122      !! ** Method  :   Set nzdf from ln_zdfexp
123      !!      nzdf = 0   explicit (time-splitting) scheme (ln_zdfexp=T)
124      !!           = 1   implicit (euler backward) scheme (ln_zdfexp=F)
125      !!      NB: rotation of lateral mixing operator or TKE & GLS schemes,
126      !!          an implicit scheme is required.
127      !!----------------------------------------------------------------------
128      USE zdftke
129      USE zdfgls
130      !!----------------------------------------------------------------------
131
132      ! Choice from ln_zdfexp already read in namelist in zdfini module
133      IF( ln_zdfexp ) THEN   ;   nzdf = 0           ! use explicit scheme
134      ELSE                   ;   nzdf = 1           ! use implicit scheme
135      ENDIF
136
137      ! Force implicit schemes
138      IF( lk_zdftke .OR. lk_zdfgls   )   nzdf = 1   ! TKE, or GLS physics
139      IF( ln_traldf_iso              )   nzdf = 1   ! iso-neutral lateral physics
140      IF( ln_traldf_hor .AND. ln_sco )   nzdf = 1   ! horizontal lateral physics in s-coordinate
141      IF( ln_zdfexp .AND. nzdf == 1 )   CALL ctl_stop( 'tra_zdf : If using the rotation of lateral mixing operator',   &
142            &                         ' GLS or TKE scheme, the implicit scheme is required, set ln_zdfexp = .false.' )
143
144      IF(lwp) THEN
145         WRITE(numout,*)
146         WRITE(numout,*) 'tra_zdf_init : vertical tracer physics scheme'
147         WRITE(numout,*) '~~~~~~~~~~~'
148         IF( nzdf ==  0 )   WRITE(numout,*) '              Explicit time-splitting scheme'
149         IF( nzdf ==  1 )   WRITE(numout,*) '              Implicit (euler backward) scheme'
150      ENDIF
151      !
152   END SUBROUTINE tra_zdf_init
153
154   !!==============================================================================
155END MODULE trazdf
Note: See TracBrowser for help on using the repository browser.