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

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf.F90 @ 4401

Last change on this file since 4401 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 8.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 trazdf_exp      ! vertical diffusion: explicit (tra_zdf_exp     routine)
23   USE trazdf_imp      ! vertical diffusion: implicit (tra_zdf_imp     routine)
24
25   USE ldftra_oce      ! ocean active tracers: lateral physics
26   USE trdmod_oce      ! ocean active tracers: lateral physics
27   USE trdtra      ! ocean tracers trends
28   USE in_out_manager  ! I/O manager
29   USE prtctl          ! Print control
30   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
31   USE lib_mpp         ! MPP library
32
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   !! * Control permutation of array indices
43#  include "oce_ftrans.h90"
44#  include "dom_oce_ftrans.h90"
45#  include "domvvl_ftrans.h90"
46#  include "zdf_oce_ftrans.h90"
47#  include "sbc_oce_ftrans.h90"
48#  include "ldftra_oce_ftrans.h90"
49
50   !! * Substitutions
51#  include "domzgr_substitute.h90"
52#  include "zdfddm_substitute.h90"
53#  include "vectopt_loop_substitute.h90"
54   !!----------------------------------------------------------------------
55   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
56   !! $Id$
57   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
58   !!----------------------------------------------------------------------
59CONTAINS
60
61   SUBROUTINE tra_zdf( kt )
62      !!----------------------------------------------------------------------
63      !!                  ***  ROUTINE tra_zdf  ***
64      !!
65      !! ** Purpose :   compute the vertical ocean tracer physics.
66      !!---------------------------------------------------------------------
67      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
68      !!
69      INTEGER  ::   ji, jj, jk           ! Dummy loop indices
70!FTRANS ztrdt ztrds :I :I :z
71      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrdt, ztrds   ! 3D workspace
72      !!---------------------------------------------------------------------
73
74      !                                          ! set time step
75      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000
76         r2dtra(:) =  rdttra(:)                          ! = rdtra (restarting with Euler time stepping)
77      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1
78         r2dtra(:) = 2. * rdttra(:)                      ! = 2 rdttra (leapfrog)
79      ENDIF
80
81      IF( l_trdtra )   THEN                    !* Save ta and sa trends
82         ALLOCATE( ztrdt(jpi,jpj,jpk) )   ;    ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
83         ALLOCATE( ztrds(jpi,jpj,jpk) )   ;    ztrds(:,:,:) = tsa(:,:,:,jp_sal)
84      ENDIF
85
86      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend
87      CASE ( 0 )    ;    CALL tra_zdf_exp( kt, 'TRA', r2dtra, nn_zdfexp, tsb, tsa, jpts )  !   explicit scheme
88      CASE ( 1 )    ;    CALL tra_zdf_imp( kt, 'TRA', r2dtra,            tsb, tsa, jpts )  !   implicit scheme
89      CASE ( -1 )                                       ! esopa: test all possibility with control print
90         CALL tra_zdf_exp( kt, 'TRA', r2dtra, nn_zdfexp, tsb, tsa, jpts )
91         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf0 - Ta: ', mask1=tmask,               &
92         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
93         CALL tra_zdf_imp( kt, 'TRA', r2dtra,            tsb, tsa, jpts ) 
94         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf1 - Ta: ', mask1=tmask,               &
95         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
96      END SELECT
97
98      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics
99#if defined key_z_first
100         DO jj = 1, jpj
101            DO ji = 1, jpi
102               DO jk = 1, jpkm1
103                  ztrdt(ji,jj,jk) = ( ( tsa(ji,jj,jk,jp_tem) - tsb(ji,jj,jk,jp_tem) ) / r2dtra(jk) ) - ztrdt(ji,jj,jk)
104                  ztrds(ji,jj,jk) = ( ( tsa(ji,jj,jk,jp_sal) - tsb(ji,jj,jk,jp_sal) ) / r2dtra(jk) ) - ztrds(ji,jj,jk)
105               END DO
106            END DO
107         END DO
108#else
109         DO jk = 1, jpkm1
110            ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / r2dtra(jk) ) - ztrdt(:,:,jk)
111            ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / r2dtra(jk) ) - ztrds(:,:,jk)
112         END DO
113#endif
114         CALL trd_tra( kt, 'TRA', jp_tem, jptra_trd_zdf, ztrdt )
115         CALL trd_tra( kt, 'TRA', jp_sal, jptra_trd_zdf, ztrds )
116         DEALLOCATE( ztrdt )      ;     DEALLOCATE( ztrds ) 
117      ENDIF
118
119      !                                          ! print mean trends (used for debugging)
120      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf  - Ta: ', mask1=tmask,               &
121         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
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#  include "zdftke_ftrans.h90"
142      !!----------------------------------------------------------------------
143
144      ! Choice from ln_zdfexp already read in namelist in zdfini module
145      IF( ln_zdfexp ) THEN   ;   nzdf = 0           ! use explicit scheme
146      ELSE                   ;   nzdf = 1           ! use implicit scheme
147      ENDIF
148
149      ! Force implicit schemes
150      IF( lk_zdftke .OR. lk_zdfgls .OR. lk_zdfkpp )   nzdf = 1      ! TKE, GLS or KPP physics
151      IF( ln_traldf_iso                           )   nzdf = 1      ! iso-neutral lateral physics
152      IF( ln_traldf_hor .AND. ln_sco              )   nzdf = 1      ! horizontal lateral physics in s-coordinate
153      IF( ln_zdfexp .AND. nzdf == 1 )   CALL ctl_stop( 'tra_zdf : If using the rotation of lateral mixing operator',   &
154            &                         ' TKE or KPP scheme, the implicit scheme is required, set ln_zdfexp = .false.' )
155
156      ! Test: esopa
157      IF( lk_esopa )    nzdf = -1                      ! All schemes used
158
159      IF(lwp) THEN
160         WRITE(numout,*)
161         WRITE(numout,*) 'tra_zdf_init : vertical tracer physics scheme'
162         WRITE(numout,*) '~~~~~~~~~~~'
163         IF( nzdf == -1 )   WRITE(numout,*) '              ESOPA test All scheme used'
164         IF( nzdf ==  0 )   WRITE(numout,*) '              Explicit time-splitting scheme'
165         IF( nzdf ==  1 )   WRITE(numout,*) '              Implicit (euler backward) scheme'
166      ENDIF
167      !
168   END SUBROUTINE tra_zdf_init
169
170   !!==============================================================================
171END MODULE trazdf
Note: See TracBrowser for help on using the repository browser.