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 @ 15740

Last change on this file since 15740 was 14086, checked in by cetlod, 4 years ago

Adding AGRIF branches into the trunk

  • Property svn:keywords set to Id
File size: 4.2 KB
RevLine 
[2030]1MODULE trczdf
2   !!==============================================================================
3   !!                 ***  MODULE  trczdf  ***
4   !! Ocean Passive tracers : vertical diffusive trends
5   !!=====================================================================
[9019]6   !! History :  9.0  ! 2005-11  (G. Madec)  Original code
[2030]7   !!       NEMO 3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
[9019]8   !!            4.0  ! 2017-04  (G. Madec)  remove the explicit case
[2030]9   !!----------------------------------------------------------------------
10#if defined key_top
11   !!----------------------------------------------------------------------
12   !!   'key_top'                                                TOP models
13   !!----------------------------------------------------------------------
[9019]14   !!   trc_zdf      : update the tracer trend with the vertical diffusion
[2030]15   !!----------------------------------------------------------------------
[14086]16   USE par_trc        ! need jptra, number of passive tracers
[5836]17   USE trc           ! ocean passive tracers variables
18   USE oce_trc       ! ocean dynamics and active tracers
19   USE trd_oce       ! trends: ocean variables
[9019]20   USE trazdf        ! tracer: vertical diffusion
[5836]21   USE trdtra        ! trends manager: tracers
[13286]22   USE prtctl        ! Print control
[2030]23
24   IMPLICIT NONE
25   PRIVATE
26
[5836]27   PUBLIC   trc_zdf         ! called by step.F90
28   
[2030]29   !!----------------------------------------------------------------------
[10067]30   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[7753]31   !! $Id$
[10068]32   !! Software governed by the CeCILL license (see ./LICENSE)
[2030]33   !!----------------------------------------------------------------------
34CONTAINS
[2715]35
[12377]36   SUBROUTINE trc_zdf( kt, Kbb, Kmm, Krhs, ptr, Kaa )
[2030]37      !!----------------------------------------------------------------------
38      !!                  ***  ROUTINE trc_zdf  ***
39      !!
[9019]40      !! ** Purpose :   compute the vertical ocean tracer physics using
41      !!              an implicit time-stepping scheme.
[2030]42      !!---------------------------------------------------------------------
[12377]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
[2030]46      !
[7753]47      INTEGER               ::  jk, jn
[2030]48      CHARACTER (len=22)    :: charout
[9019]49      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) ::   ztrtrd   ! 4D workspace
[2030]50      !!---------------------------------------------------------------------
[3294]51      !
[9124]52      IF( ln_timing )   CALL timing_start('trc_zdf')
[3294]53      !
[12377]54      IF( l_trdtrc )   ztrtrd(:,:,:,:)  = ptr(:,:,:,:,Krhs)
[9019]55      !
[12489]56      CALL tra_zdf_imp( kt, nittrc000, 'TRC', rDt_trc, Kbb, Kmm, Krhs, ptr, Kaa, jptra )    !   implicit scheme         
[9019]57      !
[3632]58      IF( l_trdtrc )   THEN                      ! save the vertical diffusive trends for further diagnostics
[2030]59         DO jn = 1, jptra
60            DO jk = 1, jpkm1
[12489]61               ztrtrd(:,:,jk,jn) = ( ( ptr(:,:,jk,jn,Kaa) - ptr(:,:,jk,jn,Kbb) ) / rDt_trc ) - ztrtrd(:,:,jk,jn)
[2030]62            END DO
[12377]63            CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_zdf, ztrtrd(:,:,:,jn) )
[2030]64         END DO
65      ENDIF
66      !                                          ! print mean trends (used for debugging)
[12377]67      IF( sn_cfctl%l_prttrc )   THEN
[9019]68         WRITE(charout, FMT="('zdf ')")
[13286]69         CALL prt_ctl_info( charout, cdcomp = 'top' )
70         CALL prt_ctl( tab4d_1=tr(:,:,:,:,Kaa), mask1=tmask, clinfo=ctrcnm, clinfo3='trd' )
[2030]71      END IF
72      !
[9124]73      IF( ln_timing )  CALL timing_stop('trc_zdf')
[3294]74      !
[2030]75   END SUBROUTINE trc_zdf
[5836]76   
[2030]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.