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 786 for branches/dev_001_GM/NEMO/OPA_SRC/TRA/tradmp.F90 – NEMO

Ignore:
Timestamp:
2008-01-10T18:11:23+01:00 (16 years ago)
Author:
gm
Message:

dev_001_GM - merge TRC-TRA on OPA only, trabbl & zpshde not done and trdmld not OK - compilation OK

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_001_GM/NEMO/OPA_SRC/TRA/tradmp.F90

    r719 r786  
    1111   !!            7.0  !  01-02  (M. Imbard)  cofdis, Original code 
    1212   !!            8.1  !  01-02  (G. Madec, E. Durand)  cleaning 
    13    !!            8.5  !  02-08  (G. Madec, E. Durand)  free form + modules 
     13   !!   NEMO     1.0  !  02-08  (G. Madec, E. Durand)  free form + modules 
     14   !!            2.4  !  08-01  (G. Madec) Merge TRA-TRC 
    1415   !!---------------------------------------------------------------------- 
    1516#if   defined key_tradmp   ||   defined key_esopa 
     
    4748   LOGICAL, PUBLIC            ::   lk_tradmp = .TRUE.     !: internal damping flag 
    4849#endif 
    49    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   strdmp   !: damping salinity trend (psu/s) 
    5050   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   resto    !: restoring coeff. on T and S (s-1) 
    5151    
     
    6262#  include "vectopt_loop_substitute.h90" 
    6363   !!---------------------------------------------------------------------- 
    64    !!   OPA 9.0 , LOCEAN-IPSL (2006)  
    65    !! $Header$  
     64   !! NEMO/OPA 2.4 , LOCEAN-IPSL (2008)  
     65   !! $Id:$  
    6666   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    6767   !!---------------------------------------------------------------------- 
     
    6969CONTAINS 
    7070 
    71    SUBROUTINE tra_dmp( kt ) 
     71   SUBROUTINE tra_dmp( kt, cdtype, ktra, ptb, pta ) 
    7272      !!---------------------------------------------------------------------- 
    7373      !!                   ***  ROUTINE tra_dmp  *** 
     
    7979      !! ** Method  :   Newtonian damping towards t_dta and s_dta computed  
    8080      !!      and add to the general tracer trends: 
    81       !!                     ta = ta + resto * (t_dta - tb) 
    82       !!                     sa = sa + resto * (s_dta - sb) 
     81      !!                     pta = pta + resto * (t_dta - ptb) 
    8382      !!         The trend is computed either throughout the water column 
    8483      !!      (nlmdmp=0) or in area of weak vertical mixing (nlmdmp=1) or 
    8584      !!      below the well mixed layer (nlmdmp=2) 
    8685      !! 
    87       !! ** Action  : - update the tracer trends (ta,sa) with the newtonian  
     86      !! ** Action  : - update the tracer trends (pta) with the newtonian  
    8887      !!                damping trends. 
    89       !!              - save the trends in (ttrd,strd) ('key_trdtra') 
    90       !!---------------------------------------------------------------------- 
    91       USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace    
    92       USE oce, ONLY :   ztrds => va   ! use va as 3D workspace    
    93       !! 
    94       INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    95       !! 
    96       INTEGER  ::   ji, jj, jk            ! dummy loop indices 
    97       REAL(wp) ::   ztest, zta, zsa       ! temporary scalars 
    98       !!---------------------------------------------------------------------- 
    99  
    100       IF( kt == nit000 )   CALL tra_dmp_init      ! Initialization 
    101  
    102       IF( l_trdtra )   THEN                       ! Save ta and sa trends 
    103          ztrdt(:,:,:) = ta(:,:,:)  
    104          ztrds(:,:,:) = sa(:,:,:)  
    105       ENDIF 
    106  
    107       ! 1. Newtonian damping trends on tracer fields 
    108       ! -------------------------------------------- 
    109       !    compute the newtonian damping trends depending on nmldmp 
    110  
    111       SELECT CASE ( nmldmp ) 
     88      !!              - save the trends in (ttrd) ('key_trdtra') 
     89      !!---------------------------------------------------------------------- 
     90      INTEGER         , INTENT(in   )                         ::   kt       ! ocean time-step index 
     91      CHARACTER(len=3), INTENT(in   )                         ::   cdtype   ! =TRA or TRC (tracer indicator) 
     92      INTEGER         , INTENT(in   )                         ::   ktra     ! tracer index 
     93      REAL(wp)        , INTENT(in   ), DIMENSION(jpi,jpj,jpk) ::   ptb      ! before tracer field 
     94      REAL(wp)        , INTENT(inout), DIMENSION(jpi,jpj,jpk) ::   pta      ! tracer trend  
     95      !! 
     96      INTEGER  ::   ji, jj, jk   ! dummy loop indices 
     97      REAL(wp) ::   zta          ! temporary scalars 
     98      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrdt   ! 3D workspace  
     99      !!---------------------------------------------------------------------- 
     100 
     101      IF( kt == nit000 .AND. ktra == jp_tem )   CALL tra_dmp_init      ! Initialization 
     102 
     103      IF( l_trdtra )   ztrdt(:,:,:) = pta(:,:,:)                      ! Save pta trend 
     104 
     105 
     106      SELECT CASE ( nmldmp )                                          ! compute the newtonian damping trends 
    112107      ! 
    113108      CASE( 0 )                ! newtonian damping throughout the water column 
     
    115110            DO jj = 2, jpjm1 
    116111               DO ji = fs_2, fs_jpim1   ! vector opt. 
    117                   zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) 
    118                   zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) 
    119                   ! add the trends to the general tracer trends 
    120                   ta(ji,jj,jk) = ta(ji,jj,jk) + zta 
    121                   sa(ji,jj,jk) = sa(ji,jj,jk) + zsa 
    122                   ! save the salinity trend (used in flx to close the salt budget) 
    123                   strdmp(ji,jj,jk) = zsa 
     112                  pta(ji,jj,jk) = pta(ji,jj,jk) + resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - ptb(ji,jj,jk) ) 
    124113               END DO 
    125114            END DO 
     
    130119            DO jj = 2, jpjm1 
    131120               DO ji = fs_2, fs_jpim1   ! vector opt. 
    132                   ztest = avt(ji,jj,jk) - 5.e-4 
    133                   IF( ztest < 0. ) THEN 
    134                      zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) 
    135                      zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) 
    136                   ELSE 
    137                      zta = 0.e0 
    138                      zsa = 0.e0 
     121                  IF( avt(ji,jj,jk) - 5.e-4 < 0. ) THEN   ;   zta = 1.e0 
     122                  ELSE                                    ;   zta = 0.e0 
    139123                  ENDIF 
    140                   ! add the trends to the general tracer trends 
    141                   ta(ji,jj,jk) = ta(ji,jj,jk) + zta 
    142                   sa(ji,jj,jk) = sa(ji,jj,jk) + zsa 
    143                   ! save the salinity trend (used in flx to close the salt budget) 
    144                   strdmp(ji,jj,jk) = zsa 
     124                  pta(ji,jj,jk) = pta(ji,jj,jk) + zta * resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - ptb(ji,jj,jk) ) 
    145125               END DO 
    146126            END DO 
     
    151131            DO jj = 2, jpjm1 
    152132               DO ji = fs_2, fs_jpim1   ! vector opt. 
    153                   IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN 
    154                      zta = resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - tb(ji,jj,jk) ) 
    155                      zsa = resto(ji,jj,jk) * ( s_dta(ji,jj,jk) - sb(ji,jj,jk) ) 
    156                   ELSE 
    157                      zta = 0.e0 
    158                      zsa = 0.e0 
     133                  IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN   ;   zta = 1.e0 
     134                  ELSE                                          ;   zta = 0.e0 
    159135                  ENDIF 
    160                   ! add the trends to the general tracer trends 
    161                   ta(ji,jj,jk) = ta(ji,jj,jk) + zta 
    162                   sa(ji,jj,jk) = sa(ji,jj,jk) + zsa 
    163                   ! save the salinity trend (used in flx to close the salt budget) 
    164                   strdmp(ji,jj,jk) = zsa 
     136                  pta(ji,jj,jk) = pta(ji,jj,jk) + zta * resto(ji,jj,jk) * ( t_dta(ji,jj,jk) - ptb(ji,jj,jk) ) 
    165137               END DO 
    166138            END DO 
     
    170142 
    171143      IF( l_trdtra )   THEN          ! save the damping tracer trends for diagnostic 
    172          ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:) 
    173          ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:) 
    174          CALL trd_mod(ztrdt, ztrds, jptra_trd_dmp, 'TRA', kt) 
     144         ztrdt(:,:,:) = pta(:,:,:) - ztrdt(:,:,:) 
     145         CALL trd_tra( kt, ktra, jpt_trd_dmp, 'TRA', ptrd3d=ztrdt) 
    175146      ENDIF 
    176147      !                              ! Control print 
    177       IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' dmp  - Ta: ', mask1=tmask,   & 
    178          &                       tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     148      IF(ln_ctl)   CALL prt_ctl( tab3d_1=pta, clinfo1=' cen2 - dmp: ', mask1=tmask, clinfo3=cdtype ) 
    179149      ! 
    180150   END SUBROUTINE tra_dmp 
     
    229199      IF( .NOT.lk_dtasal .OR. .NOT.lk_dtatem )   & 
    230200         &   CALL ctl_stop( 'no temperature and/or salinity data define key_dtatem and key_dtasal' ) 
    231  
    232       strdmp(:,:,:) = 0.e0       ! internal damping salinity trend (used in ocesbc) 
    233201 
    234202      !                          ! Damping coefficients initialization 
     
    773741   LOGICAL , PUBLIC, PARAMETER ::   lk_tradmp = .FALSE.    !: internal damping flag 
    774742CONTAINS 
    775    SUBROUTINE tra_dmp( kt )        ! Empty routine 
    776       WRITE(*,*) 'tra_dmp: You should not have seen this print! error?', kt 
     743   SUBROUTINE tra_dmp( kt, cdtype, ktra, ptb, pta ) 
     744!  SUBROUTINE tra_dmp( kt )        ! Empty routine 
     745!    INTEGER         , INTENT(in   )                         ::   kt       ! ocean time-step index 
     746      CHARACTER(len=3) ::   cdtype   ! =TRA or TRC (tracer indicator) 
     747!     INTEGER         , INTENT(in   )                         ::   ktra     ! tracer index 
     748      REAL, DIMENSION(:,:,:) ::   ptb, pta 
     749 
     750      WRITE(*,*) 'tra_dmp: You should not have seen this print! error?', kt, ktra,cdtype, ptb(1,1,1), pta(1,1,1) 
    777751   END SUBROUTINE tra_dmp 
    778752#endif 
Note: See TracChangeset for help on using the changeset viewer.