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.
Changeset 1175 for trunk/NEMO/TOP_SRC/TRP/trczdf_iso_vopt.F90 – NEMO

Ignore:
Timestamp:
2008-09-11T18:26:34+02:00 (16 years ago)
Author:
cetlod
Message:

update transport modules to take into account new trends organization, see ticket:248

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/TOP_SRC/TRP/trczdf_iso_vopt.F90

    r1152 r1175  
    11MODULE trczdf_iso_vopt 
    2    !!============================================================================== 
     2   !!====================================================================== 
    33   !!                 ***  MODULE  trczdf_iso_vopt  *** 
    44   !! Ocean passive tracers:  vertical component of the tracer mixing trend 
    5    !!============================================================================== 
    6 #if defined key_top  &&  ( defined key_ldfslp   ||   defined key_esopa ) 
    7    !!---------------------------------------------------------------------- 
    8    !!   'key_top'      and                                       TOP models 
     5   !!====================================================================== 
     6   !! History :  6.0  !  90-10 (B. Blanke)  Original code 
     7   !!            7.0  !  91-11 (G. Madec) 
     8   !!                 !  92-06 (M. Imbard) correction on tracer trend loops 
     9   !!                 !  96-01 (G. Madec) statement function for e3 
     10   !!                 !  97-05 (G. Madec) vertical component of isopycnal 
     11   !!                 !  97-07 (G. Madec) geopotential diffusion in s-coord 
     12   !!                 !  98-03  (L. Bopp MA Foujols) passive tracer generalisation 
     13   !!                 !  00-05  (MA Foujols) add lbc for tracer trends 
     14   !!                 !  00-06  (O Aumont)  correct isopycnal scheme suppress 
     15   !!                 !                     avt multiple correction 
     16   !!                 !  00-08  (G. Madec)  double diffusive mixing 
     17   !!            8.5  !  02-08  (G. Madec)  F90: Free form and module 
     18   !!            9.0  !  04-03  (C. Ethe )  adapted for passive tracers 
     19   !!                 !  06-08  (C. Deltel) Diagnose ML trends for passive tracer 
     20   !!---------------------------------------------------------------------- 
     21#if defined key_top && ( defined key_ldfslp   ||   defined key_esopa ) 
     22   !!---------------------------------------------------------------------- 
    923   !!   'key_ldfslp'                  rotation of the lateral mixing tensor 
    1024   !!---------------------------------------------------------------------- 
     
    1630   !!   trc_zdf_zdf  : 
    1731   !!---------------------------------------------------------------------- 
    18    !! * Modules used 
    19    USE oce_trc         ! ocean dynamics and tracers variables 
    20    USE trp_trc             ! ocean passive tracers variables  
    21    USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    22    USE trctrp_lec      ! passive tracers transport 
    23    USE prtctl_trc          ! Print control for debbuging 
     32   USE oce_trc               ! ocean dynamics and tracers variables 
     33   USE trp_trc                   ! ocean passive tracers variables  
     34   USE lbclnk                ! ocean lateral boundary conditions (or mpp link) 
     35   USE trctrp_lec 
     36   USE prtctl_trc            ! Print control for debbuging 
     37   USE trdmld_trc 
     38   USE trdmld_trc_oce      
    2439 
    2540   IMPLICIT NONE 
    2641   PRIVATE 
    2742 
    28    !! * Routine accessibility 
    2943   PUBLIC trc_zdf_iso_vopt   !  routine called by step.F90 
    3044 
    31    !! * Module variables 
    32    REAL(wp), DIMENSION(jpk) ::  & 
    33       rdttrc                          ! vertical profile of 2 x time-step 
     45   REAL(wp), DIMENSION(jpk) ::   rdttrc                    ! vertical profile of 2 x time-step 
     46   REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::   ztrcavg  ! workspace arrays 
    3447 
    3548   !! * Substitutions 
     
    3750   !!---------------------------------------------------------------------- 
    3851   !!   TOP 1.0 , LOCEAN-IPSL (2005)  
    39    !! $Id$  
    40    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
     52   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/TOP_SRC/TRP/trczdf_iso_vopt.F90,v 1.11 2007/02/21 12:55:33 opalod Exp $  
     53   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4154   !!---------------------------------------------------------------------- 
    4255 
     
    5063      !! ** Method  : 
    5164      !! ** Action  : 
    52       !! 
    53       !! History : 
    54       !!   8.5  !  02-08  (G. Madec)  F90: Free form and module 
    55       !!   9.0  !  04-03  (C. Ethe)   adapted for passive tracers 
    5665      !!--------------------------------------------------------------------- 
    57       !! * Arguments 
    5866      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    5967      CHARACTER (len=22) :: charout 
     
    6977      ENDIF 
    7078 
     79      IF( l_trdtrc ) THEN 
     80         ALLOCATE( ztrcavg(jpi,jpj,jpk,jptra) ) 
     81!CDIR COLLAPSE 
     82         ztrcavg(:,:,:,:) = 0.e0          ! initialisation step 
     83      ENDIF 
    7184 
    7285      ! I. vertical extra-diagonal part of the rotated tensor 
    7386      ! ----------------------------------------------------- 
    7487 
    75       CALL trc_zdf_iso 
    76  
    77       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     88      CALL trc_zdf_iso( kt ) 
     89 
     90      IF( ln_ctl ) THEN    ! print mean trends (used for debugging) 
    7891         WRITE(charout, FMT="('zdf - 1')") 
    79          CALL prt_ctl_trc_info(charout) 
    80          CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     92         CALL prt_ctl_trc_info( charout ) 
     93         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    8194      ENDIF 
    8295 
     
    8699      CALL trc_zdf_zdf( kt ) 
    87100 
    88       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     101      IF( ln_ctl ) THEN    ! print mean trends (used for debugging) 
    89102         WRITE(charout, FMT="('zdf - 2')") 
    90          CALL prt_ctl_trc_info(charout) 
    91          CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm,clinfo2='trd') 
     103         CALL prt_ctl_trc_info( charout ) 
     104         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    92105      ENDIF 
     106 
     107      IF( l_trdtrc ) DEALLOCATE( ztrcavg ) 
    93108 
    94109   END SUBROUTINE trc_zdf_iso_vopt 
     
    135150      !! 
    136151      !! ** Action  : - Update tra with before vertical diffusion trend 
    137       !!              - Save the trend in trtrd  ('key_trc_diatrd') 
    138       !! 
    139       !! History : 
    140       !!   6.0  !  90-10  (B. Blanke)  Original code 
    141       !!   7.0  !  91-11 (G. Madec) 
    142       !!        !  92-06 (M. Imbard) correction on tracer trend loops 
    143       !!        !  96-01 (G. Madec) statement function for e3 
    144       !!        !  97-05 (G. Madec) vertical component of isopycnal 
    145       !!        !  97-07 (G. Madec) geopotential diffusion in s-coord 
    146       !!        !  98-03  (L. Bopp MA Foujols) passive tracer generalisation 
    147       !!        !  00-05  (MA Foujols) add lbc for tracer trends 
    148       !!        !  00-06  (O Aumont)  correct isopycnal scheme suppress 
    149       !!        !                     avt multiple correction 
    150       !!        !  00-08  (G. Madec)  double diffusive mixing 
    151       !!   8.5  !  02-08  (G. Madec)  F90: Free form and module 
    152       !!   9.0  !  04-03  (C. Ethe )  adapted for passive tracers 
     152      !!              - Save the trend in trtrd  ('key_trdmld_trc') 
    153153      !!--------------------------------------------------------------------- 
    154       !! * Modules used 
    155154      USE oce_trc, ONLY :   zwd   => ua,  &  ! ua, va used as 
    156155                            zws   => va      ! workspace 
    157       !! * Arguments 
    158156      INTEGER, INTENT( in ) ::   kt          ! ocean time-step index 
    159  
    160       !! * Local declarations 
    161       INTEGER ::   ji, jj, jk,jn                ! dummy loop indices 
    162       REAL(wp) ::   & 
    163          zavi, zrhs                          ! temporary scalars 
     157      INTEGER ::   ji, jj, jk, jn            ! dummy loop indices 
     158      REAL(wp) ::   zavi, zrhs               ! temporary scalars 
    164159      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
    165160         zwi, zwt, zavsi                     ! temporary workspace arrays 
    166       REAL(wp) ::    ztra              !temporary scalars 
     161      REAL(wp) ::   ztra                     ! temporary scalars 
    167162#  if defined key_trc_diatrd 
    168163      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrd 
    169164#  endif 
     165      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrtrd 
    170166      !!--------------------------------------------------------------------- 
    171167 
     
    185181      ENDIF 
    186182 
    187       DO jn = 1, jptra 
     183      IF( l_trdtrc ) ALLOCATE( ztrtrd(jpi,jpj,jpk) ) 
     184 
     185      !                                                          ! =========== 
     186      DO jn = 1, jptra                                           ! tracer loop 
     187         !                                                       ! =========== 
    188188          
    189          zwd( 1 ,:,:)=0.e0     ;     zwd(jpi,:,:)=0.e0 
    190          zws( 1 ,:,:)=0.e0     ;     zws(jpi,:,:)=0.e0 
    191          zwi( 1 ,:,:)=0.e0     ;     zwi(jpi,:,:)=0.e0 
    192  
    193          zwt( 1 ,:,:)=0.e0     ;     zwt(jpi,:,:)=0.e0 
    194          zwt(  :,:,1)=0.e0     ;     zwt(:,:,jpk)= 0.e0 
    195          zavsi( 1 ,:,:)=0.e0   ;     zavsi(jpi,:,:)=0.e0  
    196          zavsi(  :,:,1)=0.e0   ;     zavsi(:,:,jpk)=0.e0 
     189!CDIR COLLAPSE 
     190         IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)          ! save trends 
     191          
     192         zwd  ( 1, :, : ) = 0.e0    ;     zwd  ( jpi, :,   : ) = 0.e0 
     193         zws  ( 1, :, : ) = 0.e0    ;     zws  ( jpi, :,   : ) = 0.e0 
     194         zwi  ( 1, :, : ) = 0.e0    ;     zwi  ( jpi, :,   : ) = 0.e0 
     195         zwt  ( 1, :, : ) = 0.e0    ;     zwt  ( jpi, :,   : ) = 0.e0 
     196         zwt  ( :, :, 1 ) = 0.e0    ;     zwt  (   :, :, jpk ) = 0.e0 
     197         zavsi( 1, :, : ) = 0.e0    ;     zavsi( jpi, :,   : ) = 0.e0  
     198         zavsi( :, :, 1 ) = 0.e0    ;     zavsi(   :, :, jpk ) = 0.e0 
    197199 
    198200#  if defined key_trc_diatrd 
     
    224226 
    225227 
    226          ! II.2 Vertical diffusion on tracer 
    227          ! ---------------------------======== 
     228         ! II.1 Vertical diffusion on tracer 
     229         ! --------------------------------- 
    228230 
    229231         ! Rebuild the Matrix as avt /= avs 
     
    313315#if defined key_trc_diatrd 
    314316         ! Compute and save the vertical diffusive passive tracer trends 
    315 #  if defined key_trcldf_iso  
     317#  if defined key_trcldf_iso 
    316318         DO jk = 1, jpkm1 
    317319            DO jj = 2, jpjm1 
     
    334336#endif 
    335337 
    336       END DO 
     338 
     339         ! III. Save vertical trend assoc. with the vertical physics for diagnostics 
     340         ! ========================================================================= 
     341         IF( l_trdtrc )   THEN 
     342 
     343            ! III.1) Deduce the full vertical diff. trend (except for vertical eiv advection) 
     344            ! N.B. tavg & savg contain the contribution from the extra diagonal part 
     345            !   of the rotated tensor (from trc_zdf_iso). 
     346            IF( ln_trcldf_iso ) THEN 
     347!CDIR COLLAPSE 
     348               DO jk = 1, jpkm1 
     349                  ztrtrd(:,:,jk) = ( (tra(:,:,jk,jn) - trb(:,:,jk,jn))/rdttrc(jk) ) - ztrtrd(:,:,jk)  & 
     350                       &           + ztrcavg(:,:,jk,jn)  
     351               END DO 
     352            ELSE 
     353!CDIR COLLAPSE 
     354               DO jk = 1, jpkm1 
     355                  ztrtrd(:,:,jk) = ( (tra(:,:,jk,jn) - trb(:,:,jk,jn))/rdttrc(jk) ) - ztrtrd(:,:,jk) 
     356               END DO 
     357            ENDIF 
     358             
     359            ! III.2) save the trends for diagnostic 
     360            ! N.B. However the purely vertical diffusion "K_z" (included here) will be deduced 
     361            !   and removed from this trend before storage. It is stored separately, so as to 
     362            !   clearly distinguish both contributions (see trd_mld) 
     363            IF (luttrd(jn)) CALL trd_mod_trc( ztrtrd, jn, jptrc_trd_zdf, kt ) 
     364 
     365         END IF 
     366         !                                                    ! =========== 
     367      END DO                                                  ! tracer loop 
     368      !                                                       ! =========== 
     369       
     370      IF( l_trdtrc ) DEALLOCATE( ztrtrd ) 
    337371 
    338372   END SUBROUTINE trc_zdf_zdf 
    339373 
    340374 
    341    SUBROUTINE trc_zdf_iso 
     375   SUBROUTINE trc_zdf_iso( kt ) 
    342376      !!---------------------------------------------------------------------- 
    343377      !!                  ***  ROUTINE trc_zdf_iso  *** 
     
    376410      !! ** Action : 
    377411      !!         Update tra arrays with the before vertical diffusion trend 
    378       !!         Save in trtrd arrays the trends if 'key_trc_diatrd' defined 
    379       !! 
    380       !! History : 
    381       !!   6.0  !  90-10  (B. Blanke)  Original code 
    382       !!   7.0  !  91-11  (G. Madec) 
    383       !!        !  92-06  (M. Imbard) correction on tracer trend loops 
    384       !!        !  96-01  (G. Madec) statement function for e3 
    385       !!        !  97-05  (G. Madec) vertical component of isopycnal 
    386       !!        !  97-07  (G. Madec) geopotential diffusion in s-coord 
    387       !!        !  98-03  (L. Bopp MA Foujols) passive tracer generalisation 
    388       !!        !  00-05  (MA Foujols) add lbc for tracer trends 
    389       !!        !  00-06  (O Aumont)  correct isopycnal scheme suppress 
    390       !!        !                     avt multiple correction 
    391       !!        !  00-08  (G. Madec)  double diffusive mixing 
    392       !!   8.5  !  02-08  (G. Madec)  F90: Free form and module 
    393       !!   9.0  !  04-03  (C. Ethe )  adapted for passive tracers 
     412      !!         Save in trtrd arrays the trends if 'key_trdmld_trc' defined 
    394413      !!--------------------------------------------------------------------- 
    395       !! * Modules used 
    396414      USE oce_trc, ONLY :   zwx => ua,  &  ! use ua, va as 
    397415                            zwy => va      ! workspace arrays 
    398416 
    399       !! * Local declarations 
    400       INTEGER ::   ji, jj, jk,jn       ! dummy loop indices 
    401       INTEGER ::   iku, ikv 
    402       REAL(wp) ::   & 
    403          ztavg,                  &  ! temporary scalars 
    404          zcoef0, zcoef3,         &  !    "         " 
    405          zcoef4,                 &  !    "         " 
    406          zbtr, zmku, zmkv,       &  !    "         " 
    407 #if defined key_trcldf_eiv 
    408          zcoeg3,                 &  !    "         " 
    409          zuwki, zvwki,           &  !    "         " 
    410          zuwk, zvwk,             &  !    "         " 
     417      INTEGER, INTENT( in ) ::   kt              ! ocean time-step index 
     418      INTEGER ::   ji, jj, jk, jn                ! dummy loop indices 
     419      INTEGER ::   iku, ikv                       
     420      REAL(wp) ::   ztavg                        ! temporary scalars 
     421      REAL(wp) ::   zcoef0, zcoef3               !    "         " 
     422      REAL(wp) ::   zcoef4                       !    "         " 
     423      REAL(wp) ::   zbtr, zmku, zmkv             !    "         " 
     424#if defined key_trcldf_eiv                        
     425      REAL(wp) ::   zcoeg3, z_hdivn_z            !    "         " 
     426      REAL(wp) ::   zuwki, zvwki                 !    "         " 
     427      REAL(wp) ::   zuwk, zvwk                   !    "         " 
    411428#endif 
    412          ztav 
    413       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
    414          zwz, zwt, ztfw             ! temporary workspace arrays 
     429      REAL(wp) ::   ztav 
     430      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zwz  ! temporary workspace arrays 
     431      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zwt 
     432      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztfw 
     433      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrtrd 
    415434      !!--------------------------------------------------------------------- 
    416435 
    417       DO jn = 1, jptra 
     436 
     437      IF( l_trdtrc ) ALLOCATE( ztrtrd(jpi,jpj,jpk) ) 
     438 
     439      !                                                          ! =========== 
     440      DO jn = 1, jptra                                           ! tracer loop 
     441         !                                                       ! =========== 
    418442 
    419443         ! 0. Local constant initialization 
    420444         ! -------------------------------- 
     445         zwx (1,:,:) = 0.e0    ;     zwx (jpi,:,:) = 0.e0 
     446         zwy (1,:,:) = 0.e0    ;     zwy (jpi,:,:) = 0.e0 
     447         zwz (1,:,:) = 0.e0    ;     zwz (jpi,:,:) = 0.e0 
     448         zwt (1,:,:) = 0.e0    ;     zwt (jpi,:,:) = 0.e0 
     449         ztfw(1,:,:) = 0.e0    ;     ztfw(jpi,:,:) = 0.e0 
     450 
     451!CDIRR COLLAPSE 
     452         IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)          ! save trends 
     453 
    421454         ztavg = 0.e0 
    422  
    423          zwx( 1 ,:,:)=0.e0     ;     zwx(jpi,:,:)=0.e0 
    424          zwy( 1 ,:,:)=0.e0     ;     zwy(jpi,:,:)=0.e0 
    425          zwz( 1 ,:,:)=0.e0     ;     zwz(jpi,:,:)=0.e0 
    426          zwt( 1 ,:,:)=0.e0     ;     zwt(jpi,:,:)=0.e0 
    427          ztfw( 1 ,:,:)=0.e0    ;     ztfw(jpi,:,:)=0.e0 
    428455 
    429456         ! I. Vertical trends associated with lateral mixing 
    430457         ! ------------------------------------------------- 
    431458         !    (excluding the vertical flux proportional to dk[t] ) 
    432  
    433459 
    434460         ! I.1 horizontal tracer gradient 
     
    460486         ENDIF 
    461487 
    462  
    463488         ! I.2 Vertical fluxes 
    464489         ! ------------------- 
     
    536561#endif 
    537562 
    538          ! I.5 Divergence of vertical fluxes added to the general tracer trend 
     563         ! I.3 Divergence of vertical fluxes added to the general tracer trend 
    539564         ! ------------------------------------------------------------------- 
    540565 
     
    549574                  ztavg = ( zwx(ji,jj,jk) - zwx(ji,jj,jk+1) ) * zbtr 
    550575                  !  WARNING trtrd(ji,jj,jk,7) used for vertical gent velocity trend  not for damping !!! 
    551                   IF (luttrd(jn)) trtrd(ji,jj,jk,ikeep(jn),9) = ztavg 
     576                  IF (luttrd(jn)) trtrd(ji,jj,jk,ikeep(jn),7) = ztavg 
    552577#   endif 
    553578                  IF (luttrd(jn)) trtrd(ji,jj,jk,ikeep(jn),6) = ztav - ztavg 
    554579#endif 
    555                END DO 
    556             END DO 
    557          END DO 
    558  
    559       END DO 
     580 
     581               END DO 
     582            END DO 
     583         END DO 
     584 
     585         ! II. Save the trends for diagnostics 
     586         ! ----------------------------------- 
     587         IF( l_trdtrc )   THEN 
     588#if defined key_trcldf_eiv 
     589 
     590            ! II.1) Compute the eiv VERTICAL trend 
     591!CDIRR COLLAPSE 
     592            DO jk = 1, jpkm1 
     593               DO jj = 2, jpjm1 
     594                  DO ji = fs_2, fs_jpim1   ! vector opt. 
     595                      
     596                     !-- Compute the eiv vertical divergence : 1/e3t ( dk[w_eiv] ) 
     597                     !   N.B. This is only possible if key_diaeiv is switched on. 
     598                     !     Else, the vertical eiv is not diagnosed, 
     599                     !     so we can only store the flux form trend d_z ( T * w_eiv ) 
     600                     !     instead of w_eiv * d_z( T ). Then, ONLY THE SUM of zonal, 
     601                     !     meridional, and vertical trends are valid. 
     602#   if defined key_diaeiv 
     603                     z_hdivn_z = ( 1./e3t(jk) ) * ( w_trc_eiv(ji,jj,jk) - w_trc_eiv(ji,jj,jk+1) ) 
     604#   else 
     605                     z_hdivn_z = 0.e0 
     606#   endif 
     607                     zbtr =  1. / ( e1t(ji,jj)*e2t(ji,jj)*fse3t(ji,jj,jk) ) 
     608                     ztrcavg(ji,jj,jk,jn) = ( zwx(ji,jj,jk) - zwx(ji,jj,jk+1) ) * zbtr & 
     609                           &                - trn(ji,jj,jk,jn) * z_hdivn_z 
     610                  END DO 
     611               END DO 
     612            END DO 
     613 
     614            ! II.2) save the trends for diagnostic 
     615            !       N.B. The other part of the computed trend is stored below for later 
     616            !         output (see trc_zdf_zdf)   
     617            IF (luttrd(jn)) CALL trd_mod_trc( ztrcavg(:,:,:,jn), jn, jptrc_trd_zei, kt ) 
     618 
     619#endif 
     620            !-- Retain only the vertical diff. trends due to the extra diagonal 
     621            !   part of the rotated tensor (i.e. remove vert. eiv from the trend) 
     622            !   N.B. ztrcavg is recycled for this purpose 
     623            ztrcavg(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:) - ztrcavg(:,:,:,jn) 
     624 
     625          END IF 
     626 
     627         !                                                       ! =========== 
     628      END DO                                                     ! tracer loop 
     629      !                                                          ! =========== 
     630 
     631      IF( l_trdtrc ) DEALLOCATE( ztrtrd ) 
    560632 
    561633   END SUBROUTINE trc_zdf_iso 
Note: See TracChangeset for help on using the changeset viewer.