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 NEMO/trunk/src/TOP/TRP – NEMO

source: NEMO/trunk/src/TOP/TRP/trczdf.F90

Last change on this file was 14086, checked in by cetlod, 3 years ago

Adding AGRIF branches into the trunk

  • Property svn:keywords set to Id
File size: 4.2 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   !!            4.0  ! 2017-04  (G. Madec)  remove the explicit case
9   !!----------------------------------------------------------------------
10#if defined key_top
11   !!----------------------------------------------------------------------
12   !!   'key_top'                                                TOP models
13   !!----------------------------------------------------------------------
14   !!   trc_zdf      : update the tracer trend with the vertical diffusion
15   !!----------------------------------------------------------------------
16   USE par_trc        ! need jptra, number of passive tracers
17   USE trc           ! ocean passive tracers variables
18   USE oce_trc       ! ocean dynamics and active tracers
19   USE trd_oce       ! trends: ocean variables
20   USE trazdf        ! tracer: vertical diffusion
21   USE trdtra        ! trends manager: tracers
22   USE prtctl        ! Print control
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   trc_zdf         ! called by step.F90
28   
29   !!----------------------------------------------------------------------
30   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
31   !! $Id$
32   !! Software governed by the CeCILL license (see ./LICENSE)
33   !!----------------------------------------------------------------------
34CONTAINS
35
36   SUBROUTINE trc_zdf( kt, Kbb, Kmm, Krhs, ptr, Kaa )
37      !!----------------------------------------------------------------------
38      !!                  ***  ROUTINE trc_zdf  ***
39      !!
40      !! ** Purpose :   compute the vertical ocean tracer physics using
41      !!              an implicit time-stepping scheme.
42      !!---------------------------------------------------------------------
43      INTEGER                                   , INTENT(in   ) ::   kt                   ! ocean time-step index
44      INTEGER                                   , INTENT(in   ) ::   Kbb, Kmm, Krhs, Kaa  ! ocean time level indices
45      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) ::   ptr                  ! passive tracers and RHS of tracer equation
46      !
47      INTEGER               ::  jk, jn
48      CHARACTER (len=22)    :: charout
49      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) ::   ztrtrd   ! 4D workspace
50      !!---------------------------------------------------------------------
51      !
52      IF( ln_timing )   CALL timing_start('trc_zdf')
53      !
54      IF( l_trdtrc )   ztrtrd(:,:,:,:)  = ptr(:,:,:,:,Krhs)
55      !
56      CALL tra_zdf_imp( kt, nittrc000, 'TRC', rDt_trc, Kbb, Kmm, Krhs, ptr, Kaa, jptra )    !   implicit scheme         
57      !
58      IF( l_trdtrc )   THEN                      ! save the vertical diffusive trends for further diagnostics
59         DO jn = 1, jptra
60            DO jk = 1, jpkm1
61               ztrtrd(:,:,jk,jn) = ( ( ptr(:,:,jk,jn,Kaa) - ptr(:,:,jk,jn,Kbb) ) / rDt_trc ) - ztrtrd(:,:,jk,jn)
62            END DO
63            CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_zdf, ztrtrd(:,:,:,jn) )
64         END DO
65      ENDIF
66      !                                          ! print mean trends (used for debugging)
67      IF( sn_cfctl%l_prttrc )   THEN
68         WRITE(charout, FMT="('zdf ')")
69         CALL prt_ctl_info( charout, cdcomp = 'top' )
70         CALL prt_ctl( tab4d_1=tr(:,:,:,:,Kaa), mask1=tmask, clinfo=ctrcnm, clinfo3='trd' )
71      END IF
72      !
73      IF( ln_timing )  CALL timing_stop('trc_zdf')
74      !
75   END SUBROUTINE trc_zdf
76   
77#else
78   !!----------------------------------------------------------------------
79   !!   Default option                                         Empty module
80   !!----------------------------------------------------------------------
81CONTAINS
82   SUBROUTINE trc_zdf( kt )
83      INTEGER, INTENT(in) :: kt 
84      WRITE(*,*) 'trc_zdf: You should not have seen this print! error?', kt
85   END SUBROUTINE trc_zdf
86#endif
87   !!==============================================================================
88END MODULE trczdf
Note: See TracBrowser for help on using the repository browser.