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.
trczdf.F90 in branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/TOP_SRC/TRP/trczdf.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: 8.9 KB
Line 
1MODULE trczdf
2   !!==============================================================================
3   !!                 ***  MODULE  trczdf  ***
4   !! Ocean Passive tracers : vertical diffusive trends
5   !!=====================================================================
6   !! History :  9.0  ! 2005-11 (G. Madec)  Original code
7   !!       NEMO 3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
8   !!----------------------------------------------------------------------
9#if defined key_top
10   !!----------------------------------------------------------------------
11   !!   'key_top'                                                TOP models
12   !!----------------------------------------------------------------------
13   !!   trc_zdf      : update the tracer trend with the lateral diffusion
14   !!   trc_zdf_ini  : initialization, namelist read, and parameters control
15   !!----------------------------------------------------------------------
16   USE trc           ! ocean passive tracers variables
17   USE oce_trc       ! ocean dynamics and active tracers
18   USE trd_oce       ! trends: ocean variables
19   USE trazdf_exp    ! vertical diffusion: explicit (tra_zdf_exp     routine)
20   USE trazdf_imp    ! vertical diffusion: implicit (tra_zdf_imp     routine)
21   USE trcldf        ! passive tracers: lateral diffusion
22   USE trdtra        ! trends manager: tracers
23   USE prtctl_trc    ! Print control
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   trc_zdf         ! called by step.F90
29   PUBLIC   trc_zdf_ini     ! called by nemogcm.F90
30   PUBLIC   trc_zdf_alloc   ! called by nemogcm.F90
31   
32   !                                        !!** Vertical diffusion (nam_trczdf) **
33   LOGICAL , PUBLIC ::   ln_trczdf_exp       !: explicit vertical diffusion scheme flag
34   INTEGER , PUBLIC ::   nn_trczdf_exp       !: number of sub-time step (explicit time stepping)
35
36   INTEGER ::   nzdf = 0               ! type vertical diffusion algorithm used
37      !                                ! defined from ln_zdf...  namlist logicals)
38   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::  r2dt   ! vertical profile time-step, = 2 rdttra
39      !                                                 ! except at nittrc000 (=rdttra) if neuler=0
40
41   !! * Substitutions
42#  include "domzgr_substitute.h90"
43#  include "zdfddm_substitute.h90"
44#  include "vectopt_loop_substitute.h90"
45   !!----------------------------------------------------------------------
46   !! NEMO/TOP 3.7 , NEMO Consortium (2015)
47   !! $Id$
48   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
49   !!----------------------------------------------------------------------
50CONTAINS
51   
52   INTEGER FUNCTION trc_zdf_alloc()
53      !!----------------------------------------------------------------------
54      !!                  ***  ROUTINE trc_zdf_alloc  ***
55      !!----------------------------------------------------------------------
56      ALLOCATE( r2dt(jpk) , STAT=trc_zdf_alloc )
57      !
58      IF( trc_zdf_alloc /= 0 )   CALL ctl_warn('trc_zdf_alloc : failed to allocate array.')
59      !
60   END FUNCTION trc_zdf_alloc
61
62
63   SUBROUTINE trc_zdf( kt )
64      !!----------------------------------------------------------------------
65      !!                  ***  ROUTINE trc_zdf  ***
66      !!
67      !! ** Purpose :   compute the vertical ocean tracer physics.
68      !!---------------------------------------------------------------------
69      INTEGER, INTENT( in ) ::  kt      ! ocean time-step index
70      !
71      INTEGER               ::  jk, jn
72      CHARACTER (len=22)    :: charout
73      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztrtrd   ! 4D workspace
74      !!---------------------------------------------------------------------
75      !
76      IF( nn_timing == 1 )  CALL timing_start('trc_zdf')
77      !
78      IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN     ! at nittrc000
79         r2dt(:) =  rdttrc(:)           ! = rdttrc (use or restarting with Euler time stepping)
80      ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN          ! at nittrc000 or nittrc000+1
81         r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog)
82      ENDIF
83
84      IF( l_trdtrc )  THEN
85         CALL wrk_alloc( jpi, jpj, jpk, jptra, ztrtrd )
86         ztrtrd(:,:,:,:)  = tra(:,:,:,:)
87      ENDIF
88
89      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend
90      CASE ( 0 ) ;  CALL tra_zdf_exp( kt, nittrc000, 'TRC', r2dt, nn_trczdf_exp, trb, tra, jptra )    !   explicit scheme
91      CASE ( 1 ) ;  CALL tra_zdf_imp( kt, nittrc000, 'TRC', r2dt,                trb, tra, jptra )    !   implicit scheme         
92      END SELECT
93
94      IF( l_trdtrc )   THEN                      ! save the vertical diffusive trends for further diagnostics
95         DO jn = 1, jptra
96            DO jk = 1, jpkm1
97               ztrtrd(:,:,jk,jn) = ( ( tra(:,:,jk,jn) - trb(:,:,jk,jn) ) / r2dt(jk) ) - ztrtrd(:,:,jk,jn)
98            END DO
99            CALL trd_tra( kt, 'TRC', jn, jptra_zdf, ztrtrd(:,:,:,jn) )
100         END DO
101         CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztrtrd )
102      ENDIF
103      !                                          ! print mean trends (used for debugging)
104      IF( ln_ctl )   THEN
105         WRITE(charout, FMT="('zdf ')") ;  CALL prt_ctl_trc_info(charout)
106                                           CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
107      END IF
108      !
109      IF( nn_timing == 1 )  CALL timing_stop('trc_zdf')
110      !
111   END SUBROUTINE trc_zdf
112
113
114   SUBROUTINE trc_zdf_ini
115      !!----------------------------------------------------------------------
116      !!                 ***  ROUTINE trc_zdf_ini  ***
117      !!
118      !! ** Purpose :   Choose the vertical mixing scheme
119      !!
120      !! ** Method  :   Set nzdf from ln_zdfexp
121      !!      nzdf = 0   explicit (time-splitting) scheme (ln_trczdf_exp=T)
122      !!           = 1   implicit (euler backward) scheme (ln_trczdf_exp=F)
123      !!      NB: The implicit scheme is required when using :
124      !!             - rotated lateral mixing operator
125      !!             - TKE, GLS vertical mixing scheme
126      !!----------------------------------------------------------------------
127      INTEGER ::  ios                 ! Local integer output status for namelist read
128      !!
129      NAMELIST/namtrc_zdf/ ln_trczdf_exp  , nn_trczdf_exp
130      !!----------------------------------------------------------------------
131      !
132      REWIND( numnat_ref )             ! namtrc_zdf in reference namelist
133      READ  ( numnat_ref, namtrc_zdf, IOSTAT = ios, ERR = 905)
134905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in reference namelist', lwp )
135      !
136      REWIND( numnat_cfg )             ! namtrc_zdf in configuration namelist
137      READ  ( numnat_cfg, namtrc_zdf, IOSTAT = ios, ERR = 906 )
138906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in configuration namelist', lwp )
139      IF(lwm) WRITE ( numont, namtrc_zdf )
140      !
141      IF(lwp) THEN                     ! Control print
142         WRITE(numout,*)
143         WRITE(numout,*) '   Namelist namtrc_zdf : set vertical diffusion  parameters'
144         WRITE(numout,*) '      time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp
145         WRITE(numout,*) '      number of time step              nn_trczdf_exp = ', nn_trczdf_exp
146      ENDIF
147
148      !                                ! Define the vertical tracer physics scheme
149      IF( ln_trczdf_exp ) THEN   ;   nzdf = 0     ! explicit scheme
150      ELSE                       ;   nzdf = 1     ! implicit scheme
151      ENDIF
152
153      !                                ! Force implicit schemes
154      IF( ln_trcldf_iso              )   nzdf = 1      ! iso-neutral lateral physics
155      IF( ln_trcldf_hor .AND. ln_sco )   nzdf = 1      ! horizontal lateral physics in s-coordinate
156#if defined key_zdftke || defined key_zdfgls 
157                                         nzdf = 1      ! TKE or GLS physics       
158#endif
159      IF( ln_trczdf_exp .AND. nzdf == 1 )  & 
160         CALL ctl_stop( 'trc_zdf : If using the rotated lateral mixing operator or TKE, GLS vertical scheme ', &
161            &           '          the implicit scheme is required, set ln_trczdf_exp = .false.' )
162
163      IF(lwp) THEN
164         WRITE(numout,*)
165         WRITE(numout,*) 'trc:zdf_ctl : vertical passive tracer physics scheme'
166         WRITE(numout,*) '~~~~~~~~~~~'
167         IF( nzdf ==  0 )   WRITE(numout,*) '              Explicit time-splitting scheme'
168         IF( nzdf ==  1 )   WRITE(numout,*) '              Implicit (euler backward) scheme'
169      ENDIF
170      !
171   END SUBROUTINE trc_zdf_ini
172   
173#else
174   !!----------------------------------------------------------------------
175   !!   Default option                                         Empty module
176   !!----------------------------------------------------------------------
177CONTAINS
178   SUBROUTINE trc_zdf( kt )
179      INTEGER, INTENT(in) :: kt 
180      WRITE(*,*) 'trc_zdf: You should not have seen this print! error?', kt
181   END SUBROUTINE trc_zdf
182#endif
183   !!==============================================================================
184END MODULE trczdf
Note: See TracBrowser for help on using the repository browser.