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 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf.F90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (8 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf.F90

    r3294 r6225  
    99 
    1010   !!---------------------------------------------------------------------- 
    11    !!   tra_zdf      : Update the tracer trend with the vertical diffusion 
    12    !!   tra_zdf_init : initialisation of the computation 
     11   !!   tra_zdf       : Update the tracer trend with the vertical diffusion 
     12   !!   tra_zdf_init  : initialisation of the computation 
    1313   !!---------------------------------------------------------------------- 
    14    USE oce             ! ocean dynamics and tracers variables 
    15    USE dom_oce         ! ocean space and time domain variables  
    16    USE domvvl          ! variable volume 
    17    USE phycst          ! physical constant 
    18    USE zdf_oce         ! ocean vertical physics variables 
    19    USE sbc_oce         ! surface boundary condition: ocean 
    20    USE dynspg_oce 
    21  
    22    USE trazdf_exp      ! vertical diffusion: explicit (tra_zdf_exp     routine) 
    23    USE trazdf_imp      ! vertical diffusion: implicit (tra_zdf_imp     routine) 
    24  
    25    USE ldftra_oce      ! ocean active tracers: lateral physics 
    26    USE trdmod_oce      ! ocean active tracers: lateral physics 
    27    USE trdtra      ! ocean tracers trends  
    28    USE in_out_manager  ! I/O manager 
    29    USE prtctl          ! Print control 
    30    USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    31    USE lib_mpp         ! MPP library 
    32    USE wrk_nemo        ! Memory allocation 
    33    USE timing          ! Timing 
    34  
     14   USE oce            ! ocean dynamics and tracers variables 
     15   USE dom_oce        ! ocean space and time domain variables  
     16   USE domvvl         ! variable volume 
     17   USE phycst         ! physical constant 
     18   USE zdf_oce        ! ocean vertical physics variables 
     19   USE sbc_oce        ! surface boundary condition: ocean 
     20   USE ldftra         ! lateral diffusion: eddy diffusivity 
     21   USE ldfslp         ! lateral diffusion: iso-neutral slope  
     22   USE trazdf_exp     ! vertical diffusion: explicit (tra_zdf_exp routine) 
     23   USE trazdf_imp     ! vertical diffusion: implicit (tra_zdf_imp routine) 
     24   USE trd_oce        ! trends: ocean variables 
     25   USE trdtra         ! trends: tracer trend manager 
     26   ! 
     27   USE in_out_manager ! I/O manager 
     28   USE prtctl         ! Print control 
     29   USE lbclnk         ! ocean lateral boundary conditions (or mpp link) 
     30   USE lib_mpp        ! MPP library 
     31   USE wrk_nemo       ! Memory allocation 
     32   USE timing         ! Timing 
    3533 
    3634   IMPLICIT NONE 
     
    4341 
    4442   !! * Substitutions 
    45 #  include "domzgr_substitute.h90" 
    4643#  include "zdfddm_substitute.h90" 
    4744#  include "vectopt_loop_substitute.h90" 
    4845   !!---------------------------------------------------------------------- 
    49    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     46   !! NEMO/OPA 3.7 , NEMO Consortium (2015) 
    5047   !! $Id$ 
    5148   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    6057      !!--------------------------------------------------------------------- 
    6158      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    62       !! 
     59      ! 
    6360      INTEGER  ::   jk                   ! Dummy loop indices 
    6461      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrdt, ztrds   ! 3D workspace 
     
    6865      ! 
    6966      IF( neuler == 0 .AND. kt == nit000 ) THEN     ! at nit000 
    70          r2dtra(:) =  rdttra(:)                          ! = rdtra (restarting with Euler time stepping) 
     67         r2dt =  rdt                          ! = rdt (restarting with Euler time stepping) 
    7168      ELSEIF( kt <= nit000 + 1) THEN                ! at nit000 or nit000+1 
    72          r2dtra(:) = 2. * rdttra(:)                      ! = 2 rdttra (leapfrog) 
     69         r2dt = 2. * rdt                      ! = 2 rdt (leapfrog) 
    7370      ENDIF 
    74  
     71      ! 
    7572      IF( l_trdtra )   THEN                    !* Save ta and sa trends 
    7673         CALL wrk_alloc( jpi, jpj, jpk, ztrdt, ztrds ) 
     
    7875         ztrds(:,:,:) = tsa(:,:,:,jp_sal) 
    7976      ENDIF 
    80  
     77      ! 
    8178      SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend 
    82       CASE ( 0 )    ;    CALL tra_zdf_exp( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb, tsa, jpts )  !   explicit scheme  
    83       CASE ( 1 )    ;    CALL tra_zdf_imp( kt, nit000, 'TRA', r2dtra,            tsb, tsa, jpts )  !   implicit scheme  
    84       CASE ( -1 )                                       ! esopa: test all possibility with control print 
    85          CALL tra_zdf_exp( kt, nit000, 'TRA', r2dtra, nn_zdfexp, tsb, tsa, jpts ) 
    86          CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf0 - Ta: ', mask1=tmask,               & 
    87          &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    88          CALL tra_zdf_imp( kt, nit000, 'TRA', r2dtra,            tsb, tsa, jpts )  
    89          CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf1 - Ta: ', mask1=tmask,               & 
    90          &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
     79      CASE ( 0 )    ;    CALL tra_zdf_exp( kt, nit000, 'TRA', r2dt, nn_zdfexp, tsb, tsa, jpts )  !   explicit scheme  
     80      CASE ( 1 )    ;    CALL tra_zdf_imp( kt, nit000, 'TRA', r2dt,            tsb, tsa, jpts )  !   implicit scheme  
    9181      END SELECT 
     82!!gm WHY here !   and I don't like that ! 
     83      ! DRAKKAR SSS control { 
     84      ! JMM avoid negative salinities near river outlet ! Ugly fix 
     85      ! JMM : restore negative salinities to small salinities: 
     86      WHERE( tsa(:,:,:,jp_sal) < 0._wp )   tsa(:,:,:,jp_sal) = 0.1_wp 
     87!!gm 
    9288 
    9389      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics 
    9490         DO jk = 1, jpkm1 
    95             ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / r2dtra(jk) ) - ztrdt(:,:,jk) 
    96             ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / r2dtra(jk) ) - ztrds(:,:,jk) 
     91            ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / r2dt ) - ztrdt(:,:,jk) 
     92            ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / r2dt ) - ztrds(:,:,jk) 
    9793         END DO 
    98          CALL trd_tra( kt, 'TRA', jp_tem, jptra_trd_zdf, ztrdt ) 
    99          CALL trd_tra( kt, 'TRA', jp_sal, jptra_trd_zdf, ztrds ) 
     94!!gm this should be moved in trdtra.F90 and done on all trends 
     95         CALL lbc_lnk( ztrdt, 'T', 1. ) 
     96         CALL lbc_lnk( ztrds, 'T', 1. ) 
     97!!gm 
     98         CALL trd_tra( kt, 'TRA', jp_tem, jptra_zdf, ztrdt ) 
     99         CALL trd_tra( kt, 'TRA', jp_sal, jptra_zdf, ztrds ) 
    100100         CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds ) 
    101101      ENDIF 
    102  
    103102      !                                          ! print mean trends (used for debugging) 
    104103      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' zdf  - Ta: ', mask1=tmask,               & 
     
    119118      !!      nzdf = 0   explicit (time-splitting) scheme (ln_zdfexp=T) 
    120119      !!           = 1   implicit (euler backward) scheme (ln_zdfexp=F) 
    121       !!      NB: rotation of lateral mixing operator or TKE or KPP scheme, 
    122       !!      the implicit scheme is required. 
     120      !!      NB: rotation of lateral mixing operator or TKE & GLS schemes, 
     121      !!          an implicit scheme is required. 
    123122      !!---------------------------------------------------------------------- 
    124123      USE zdftke 
    125124      USE zdfgls 
    126       USE zdfkpp 
    127125      !!---------------------------------------------------------------------- 
    128  
     126      ! 
    129127      ! Choice from ln_zdfexp already read in namelist in zdfini module 
    130128      IF( ln_zdfexp ) THEN   ;   nzdf = 0           ! use explicit scheme 
    131129      ELSE                   ;   nzdf = 1           ! use implicit scheme 
    132130      ENDIF 
    133  
     131      ! 
    134132      ! Force implicit schemes 
    135       IF( lk_zdftke .OR. lk_zdfgls .OR. lk_zdfkpp )   nzdf = 1      ! TKE, GLS or KPP physics 
    136       IF( ln_traldf_iso                           )   nzdf = 1      ! iso-neutral lateral physics 
    137       IF( ln_traldf_hor .AND. ln_sco              )   nzdf = 1      ! horizontal lateral physics in s-coordinate 
     133      IF( lk_zdftke .OR. lk_zdfgls   )   nzdf = 1   ! TKE, or GLS physics 
     134      IF( ln_traldf_iso              )   nzdf = 1   ! iso-neutral lateral physics 
     135      IF( ln_traldf_hor .AND. ln_sco )   nzdf = 1   ! horizontal lateral physics in s-coordinate 
    138136      IF( ln_zdfexp .AND. nzdf == 1 )   CALL ctl_stop( 'tra_zdf : If using the rotation of lateral mixing operator',   & 
    139             &                         ' TKE or KPP scheme, the implicit scheme is required, set ln_zdfexp = .false.' ) 
    140  
    141       ! Test: esopa 
    142       IF( lk_esopa )    nzdf = -1                      ! All schemes used 
    143  
     137            &                         ' GLS or TKE scheme, the implicit scheme is required, set ln_zdfexp = .false.' ) 
     138            ! 
    144139      IF(lwp) THEN 
    145140         WRITE(numout,*) 
    146141         WRITE(numout,*) 'tra_zdf_init : vertical tracer physics scheme' 
    147142         WRITE(numout,*) '~~~~~~~~~~~' 
    148          IF( nzdf == -1 )   WRITE(numout,*) '              ESOPA test All scheme used' 
    149143         IF( nzdf ==  0 )   WRITE(numout,*) '              Explicit time-splitting scheme' 
    150144         IF( nzdf ==  1 )   WRITE(numout,*) '              Implicit (euler backward) scheme' 
Note: See TracChangeset for help on using the changeset viewer.