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

source: trunk/NEMO/OPA_SRC/TRA/trazdf.F90 @ 484

Last change on this file since 484 was 458, checked in by opalod, 18 years ago

nemo_v1_update_049:RB: reorganization of tracers part, remove traadv_cen2_atsk.h90 traldf_iso_zps.F90 trazdf_iso.F90 trazdf_iso_vopt.F90, change atsk routines to jki, add control modules traadv, traldf, trazdf

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
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 :
7   !!   9.0  !  05-11  (G. Madec)  Original code
8   !!----------------------------------------------------------------------
9   !!   tra_zdf      : Update the tracer trend with the vertical diffusion
10   !!       zdf_ctl  : ???
11   !!----------------------------------------------------------------------
12   !! * Modules used
13   USE oce             ! ocean dynamics and tracers variables
14   USE dom_oce         ! ocean space and time domain variables
15   USE zdf_oce         ! ocean vertical physics variables
16
17   USE trazdf_exp      ! vertical diffusion: explicit (tra_zdf_exp     routine)
18   USE trazdf_imp      ! vertical diffusion: implicit (tra_zdf_imp     routine)
19   USE trazdf_imp_jki  ! vertical diffusion  implicit (tra_zdf_imp_jki routine)
20
21   USE ldftra_oce      ! ocean active tracers: lateral physics
22   USE trdmod          ! ocean active tracers trends
23   USE trdmod_oce      ! ocean variables trends
24   USE in_out_manager  ! I/O manager
25   USE prtctl          ! Print control
26
27   IMPLICIT NONE
28   PRIVATE
29
30   !! * Routine accessibility
31   PUBLIC tra_zdf   !  routine called by step.F90
32
33   !! * module variables
34   INTEGER ::                        &
35      nzdf = 0                         ! type vertical diffusion algorithm used
36      !                                ! defined from ln_zdf...  namlist logicals)
37
38   !! * Module variables
39   REAL(wp), DIMENSION(jpk) ::  &
40      r2dt                          ! vertical profile time-step, = 2 rdttra
41      !                             ! except at nit000 (=rdttra) if neuler=0
42
43   !! * Substitutions
44#  include "domzgr_substitute.h90"
45#  include "zdfddm_substitute.h90"
46#  include "vectopt_loop_substitute.h90"
47   !!----------------------------------------------------------------------
48   !!  OPA 9.0 , LOCEAN-IPSL (2005)
49   !!----------------------------------------------------------------------
50
51CONTAINS
52   
53   SUBROUTINE tra_zdf( kt )
54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE tra_zdf  ***
56      !!
57      !! ** Purpose :   compute the vertical ocean tracer physics.
58      !! ** Method  :
59      !! ** Action  :
60      !!
61      !!---------------------------------------------------------------------
62      !! * Arguments
63      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
64
65      !! * local declarations
66      INTEGER  ::   jk                   ! Dummy loop indices
67      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &
68         ztrdt, ztrds                         ! 3D temporary workspace
69      !!---------------------------------------------------------------------
70
71      IF( kt == nit000 )   CALL zdf_ctl          ! initialisation & control of options
72
73      !                                          ! set time step
74      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000
75         r2dt(:) =  rdttra(:)                          ! = rdtra (restarting with Euler time stepping)
76      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1
77         r2dt(:) = 2. * rdttra(:)                      ! = 2 rdttra (leapfrog)
78      ENDIF
79
80
81      IF( l_trdtra )   THEN                      ! temporary save of ta and sa trends
82         ztrdt(:,:,:) = ta(:,:,:)
83         ztrds(:,:,:) = sa(:,:,:)
84      ENDIF
85
86      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend
87      CASE ( -1 )                                       ! esopa: test all possibility with control print
88         CALL tra_zdf_exp    ( kt, r2dt )
89         CALL prt_ctl( tab3d_1=ta, clinfo1=' zdf0 - Ta: ', mask1=tmask,               &
90            &          tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
91         CALL tra_zdf_imp    ( kt, r2dt )
92         CALL prt_ctl( tab3d_1=ta, clinfo1=' zdf1 - Ta: ', mask1=tmask,               &
93            &          tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
94         CALL tra_zdf_imp_jki( kt, r2dt )
95         CALL prt_ctl( tab3d_1=ta, clinfo1=' zdf2 - Ta: ', mask1=tmask,               &
96            &          tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
97
98      CASE ( 0 )                                       ! explicit scheme
99         CALL tra_zdf_exp    ( kt, r2dt )
100         IF( l_trdtra )   THEN                         ! save the vertical diffusive trends for further diagnostics
101            ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:)
102            ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:)
103            CALL trd_mod( ztrdt, ztrds, jpttdzdf, 'TRA', kt )
104         ENDIF
105
106      CASE ( 1 )                                       ! implicit scheme (k-j-i loop)
107         CALL tra_zdf_imp    ( kt, r2dt )
108         IF( l_trdtra )   THEN                         ! save the vertical diffusive trends for further diagnostics
109            DO jk = 1, jpkm1
110               ztrdt(:,:,jk) = ( ( ta(:,:,jk) - tb(:,:,jk) ) / r2dt(jk) ) - ztrdt(:,:,jk)
111               ztrds(:,:,jk) = ( ( sa(:,:,jk) - sb(:,:,jk) ) / r2dt(jk) ) - ztrds(:,:,jk)
112            END DO
113            CALL trd_mod( ztrdt, ztrds, jpttdzdf, 'TRA', kt )
114         ENDIF
115
116      CASE ( 2 )                                       ! implicit scheme (j-k-i loop)
117         CALL tra_zdf_imp_jki( kt, r2dt )
118         IF( l_trdtra )   THEN                         ! save the vertical diffusive trends for further diagnostics
119            DO jk = 1, jpkm1
120               ztrdt(:,:,jk) = ( ( ta(:,:,jk) - tb(:,:,jk) ) / r2dt(jk) ) - ztrdt(:,:,jk)
121               ztrds(:,:,jk) = ( ( sa(:,:,jk) - sb(:,:,jk) ) / r2dt(jk) ) - ztrds(:,:,jk)
122            END DO
123            CALL trd_mod( ztrdt, ztrds, jpttdzdf, 'TRA', kt )
124         ENDIF
125
126      END SELECT
127
128      !                                                ! print mean trends (used for debugging)
129      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' zdf  - Ta: ', mask1=tmask,               &
130         &                       tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
131
132   END SUBROUTINE tra_zdf
133
134
135   SUBROUTINE zdf_ctl
136      !!----------------------------------------------------------------------
137      !!                 ***  ROUTINE zdf_ctl  ***
138      !!
139      !! ** Purpose :   Choose the vertical mixing scheme
140      !!
141      !! ** Method  :   Set nzdf from ln_zdfexp and 'key_mpp_omp'.
142      !!      nzdf = 0   explicit (time-splitting) scheme (ln_zdfexp=T)
143      !!           = 1   implicit (euler backward) scheme (ln_zdfexp=F)
144      !!           = 2   implicit (euler backward) scheme with j-k-i loops
145      !!                 (ln_zdfexp=T and 'key_mpp_omp')
146      !!      NB: rotation of lateral mixing operator or TKE or KPP scheme,
147      !!      the implicit scheme is required.
148      !!
149      !!----------------------------------------------------------------------
150      !! * Module used
151      USE zdftke
152      USE zdfkpp
153      !!----------------------------------------------------------------------
154
155      !  Define the vertical tracer physics scheme
156      ! ==========================================
157
158      ! Choice from ln_zdfexp already read in namelist in zdfini module
159      IF( ln_zdfexp ) THEN               ! use explicit scheme
160         nzdf = 0
161      ELSE                               ! use implicit scheme
162         nzdf = 1
163      ENDIF
164
165      ! Force implicit schemes
166      IF( lk_zdftke .OR. lk_zdfkpp   )   nzdf = 1      ! TKE or KPP physics
167      IF( ln_traldf_iso              )   nzdf = 1      ! iso-neutral lateral physics
168      IF( ln_traldf_hor .AND. ln_sco )   nzdf = 1      ! horizontal lateral physics in s-coordinate
169
170      ! NEC autotasking / OpenMP
171#if defined key_mpp_omp
172      IF( nzdf == 1 )   nzdf = 2                       ! j-k-i loop
173#endif
174
175      ! Test: esopa
176      IF( lk_esopa )    nzdf = -1                      ! All schemes used
177
178      IF(lwp) THEN
179         WRITE(numout,*)
180         WRITE(numout,*) 'tra:zdf_ctl : vertical tracer physics scheme'
181         WRITE(numout,*) '~~~~~~~~~~~'
182         IF( nzdf == -1 )   WRITE(numout,*) '              ESOPA test All scheme used'
183         IF( nzdf ==  0 )   WRITE(numout,*) '              Explicit time-splitting scheme'
184         IF( nzdf ==  1 )   WRITE(numout,*) '              Implicit (euler backward) scheme'
185         IF( nzdf ==  2 )   WRITE(numout,*) '              Implicit (euler backward) scheme with j-k-i loops'
186      ENDIF
187
188   END SUBROUTINE zdf_ctl
189
190   !!==============================================================================
191END MODULE trazdf
Note: See TracBrowser for help on using the repository browser.