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 8215 for branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

Ignore:
Timestamp:
2017-06-25T12:26:32+02:00 (7 years ago)
Author:
gm
Message:

#1911 (ENHANCE-09): PART 0 - phasing with branch dev_r7832_HPC09_ZDF revision 8214

Location:
branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/TOP_SRC/TRP
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/TOP_SRC/TRP/trcbbl.F90

    r7753 r8215  
    55   !!                                  layer scheme 
    66   !!====================================================================== 
    7    !!============================================================================== 
    87   !! History :  OPA  !  1996-06  (L. Mortier)  Original code 
    98   !!            8.0  !  1997-11  (G. Madec)    Optimization 
     
    1312   !!             -   !  2010-04  (G. Madec)  Campin & Goosse advective bbl  
    1413   !!             -   !  2010-06  (C. Ethe, G. Madec)  merge TRA-TRC 
     14   !!            4.0  !  2017-04  (G. Madec)  ln_trabbl namelist variable instead of a CPP key 
    1515   !!---------------------------------------------------------------------- 
    16 #if  defined key_top &&  defined key_trabbl  
     16#if  defined key_top 
    1717   !!---------------------------------------------------------------------- 
    18    !!   'key_trabbl                      diffusive or/and adevective bottom boundary layer 
     18   !!   'key_top'                                                TOP models 
    1919   !!---------------------------------------------------------------------- 
    20    !!    trc_bbl       : update the tracer trends due to the bottom boundary layer (advective and/or diffusive) 
     20   !!    trc_bbl      : update the tracer trends due to the bottom boundary layer (advective and/or diffusive) 
    2121   !!---------------------------------------------------------------------- 
    22    USE oce_trc             ! ocean dynamics and active tracers variables 
    23    USE trc                 ! ocean passive tracers variables 
    24    USE trabbl              !  
    25    USE prtctl_trc          ! Print control for debbuging 
    26    USE trd_oce 
    27    USE trdtra 
     22   USE oce_trc        ! ocean dynamics and active tracers variables 
     23   USE trc            ! ocean passive tracers variables 
     24   USE trd_oce        ! trends: ocean variables 
     25   USE trdtra         ! tracer trends 
     26   USE trabbl         ! bottom boundary layer  
     27   USE prtctl_trc     ! Print control for debbuging 
    2828 
    29    PUBLIC   trc_bbl       !  routine called by step.F90 
     29   PUBLIC   trc_bbl   !  routine called by trctrp.F90 
    3030 
    3131   !!---------------------------------------------------------------------- 
    32    !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     32   !! NEMO/TOP 4.0 , NEMO Consortium (2017) 
    3333   !! $Id$  
    3434   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    3535   !!---------------------------------------------------------------------- 
    36  
    3736CONTAINS 
    38  
    3937 
    4038   SUBROUTINE trc_bbl( kt ) 
     
    7371         ENDIF 
    7472         ! 
    75       END IF 
     73      ENDIF 
    7674 
    7775      !* Advective bbl : bbl upstream advective trends added to the tracer trends 
     
    8482         ENDIF 
    8583         ! 
    86       END IF 
     84      ENDIF 
    8785 
    8886      IF( l_trdtrc )   THEN                      ! save the horizontal diffusive trends for further diagnostics 
     
    9896   END SUBROUTINE trc_bbl 
    9997 
    100 #else 
    101    !!---------------------------------------------------------------------- 
    102    !!   Dummy module :                      No bottom boundary layer scheme 
    103    !!---------------------------------------------------------------------- 
    104 CONTAINS 
    105    SUBROUTINE trc_bbl( kt )              ! Empty routine 
    106       WRITE(*,*) 'tra_bbl: You should not have seen this print! error?', kt 
    107    END SUBROUTINE trc_bbl 
    10898#endif 
    10999 
  • branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90

    r7646 r8215  
    121121                     DO jj = 2, jpjm1 
    122122                        DO ji = fs_2, fs_jpim1   ! vector opt. 
    123                            IF( avt(ji,jj,jk) <= 5.e-4_wp )  THEN  
     123                           IF( avs(ji,jj,jk) <= 5.e-4_wp )  THEN  
    124124                              tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) ) 
    125125                           ENDIF 
  • branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r7646 r8215  
    1515   USE oce_trc         ! ocean dynamics and active tracers variables 
    1616   USE trc             ! ocean passive tracers variables  
    17    USE trabbl          ! bottom boundary layer               (trc_bbl routine) 
    1817   USE trcbbl          ! bottom boundary layer               (trc_bbl routine) 
    1918   USE trcdmp          ! internal damping                    (trc_dmp routine) 
     
    6362         ! 
    6463                                CALL trc_sbc    ( kt )      ! surface boundary condition 
    65          IF( lk_trabbl )        CALL trc_bbl    ( kt )      ! advective (and/or diffusive) bottom boundary layer scheme 
     64         IF( ln_trabbl )        CALL trc_bbl    ( kt )      ! advective (and/or diffusive) bottom boundary layer scheme 
    6665         IF( ln_trcdmp )        CALL trc_dmp    ( kt )      ! internal damping trends 
    6766         IF( ln_bdy )           CALL trc_bdy_dmp( kt )      ! BDY damping trends 
  • branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/TOP_SRC/TRP/trczdf.F90

    r7753 r8215  
    44   !! Ocean Passive tracers : vertical diffusive trends  
    55   !!===================================================================== 
    6    !! History :  9.0  ! 2005-11 (G. Madec)  Original code 
     6   !! History :  9.0  ! 2005-11  (G. Madec)  Original code 
    77   !!       NEMO 3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA  
     8   !!            4.0  ! 2017-04  (G. Madec)  remove the explicit case 
    89   !!---------------------------------------------------------------------- 
    910#if defined key_top 
     
    1112   !!   'key_top'                                                TOP models 
    1213   !!---------------------------------------------------------------------- 
    13    !!   trc_zdf      : update the tracer trend with the lateral diffusion 
    14    !!   trc_zdf_ini  : initialization, namelist read, and parameters control 
     14   !!   trc_zdf      : update the tracer trend with the vertical diffusion 
    1515   !!---------------------------------------------------------------------- 
    1616   USE trc           ! ocean passive tracers variables 
    1717   USE oce_trc       ! ocean dynamics and active tracers 
    1818   USE trd_oce       ! trends: ocean variables 
    19    USE trazdf_exp    ! vertical diffusion: explicit (tra_zdf_exp     routine) 
    20    USE trazdf_imp    ! vertical diffusion: implicit (tra_zdf_imp     routine) 
     19   USE trazdf        ! tracer: vertical diffusion 
     20!!gm do we really need this ? 
    2121   USE trcldf        ! passive tracers: lateral diffusion 
     22!!gm 
    2223   USE trdtra        ! trends manager: tracers  
    2324   USE prtctl_trc    ! Print control 
     
    2728 
    2829   PUBLIC   trc_zdf         ! called by step.F90  
    29    PUBLIC   trc_zdf_ini     ! called by nemogcm.F90  
    3030    
    31    !                                        !!** Vertical diffusion (nam_trczdf) ** 
    32    LOGICAL , PUBLIC ::   ln_trczdf_exp       !: explicit vertical diffusion scheme flag 
    33    INTEGER , PUBLIC ::   nn_trczdf_exp       !: number of sub-time step (explicit time stepping) 
    34  
    35    INTEGER ::   nzdf = 0               ! type vertical diffusion algorithm used 
    36       !                                ! defined from ln_zdf...  namlist logicals) 
    37    !! * Substitutions 
    38 #  include "zdfddm_substitute.h90" 
    39 #  include "vectopt_loop_substitute.h90" 
    4031   !!---------------------------------------------------------------------- 
    4132   !! NEMO/TOP 3.7 , NEMO Consortium (2015) 
     
    4940      !!                  ***  ROUTINE trc_zdf  *** 
    5041      !! 
    51       !! ** Purpose :   compute the vertical ocean tracer physics. 
     42      !! ** Purpose :   compute the vertical ocean tracer physics using 
     43      !!              an implicit time-stepping scheme. 
    5244      !!--------------------------------------------------------------------- 
    5345      INTEGER, INTENT( in ) ::  kt      ! ocean time-step index 
     
    5547      INTEGER               ::  jk, jn 
    5648      CHARACTER (len=22)    :: charout 
    57       REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztrtrd   ! 4D workspace 
     49      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) ::   ztrtrd   ! 4D workspace 
    5850      !!--------------------------------------------------------------------- 
    5951      ! 
    6052      IF( nn_timing == 1 )  CALL timing_start('trc_zdf') 
    6153      ! 
    62       IF( l_trdtrc )  THEN 
    63          CALL wrk_alloc( jpi, jpj, jpk, jptra, ztrtrd ) 
    64          ztrtrd(:,:,:,:)  = tra(:,:,:,:) 
    65       ENDIF 
    66  
    67       SELECT CASE ( nzdf )                       ! compute lateral mixing trend and add it to the general trend 
    68       CASE ( 0 ) ;  CALL tra_zdf_exp( kt, nittrc000, 'TRC', r2dttrc, nn_trczdf_exp, trb, tra, jptra )    !   explicit scheme  
    69       CASE ( 1 ) ;  CALL tra_zdf_imp( kt, nittrc000, 'TRC', r2dttrc,                trb, tra, jptra )    !   implicit scheme           
    70       END SELECT 
    71  
     54      IF( l_trdtrc )   ztrtrd(:,:,:,:)  = tra(:,:,:,:) 
     55      ! 
     56      CALL tra_zdf_imp( kt, nittrc000, 'TRC', r2dttrc, trb, tra, jptra )    !   implicit scheme           
     57      ! 
    7258      IF( l_trdtrc )   THEN                      ! save the vertical diffusive trends for further diagnostics 
    7359         DO jn = 1, jptra 
     
    7763            CALL trd_tra( kt, 'TRC', jn, jptra_zdf, ztrtrd(:,:,:,jn) ) 
    7864         END DO 
    79          CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztrtrd ) 
    8065      ENDIF 
    8166      !                                          ! print mean trends (used for debugging) 
    8267      IF( ln_ctl )   THEN 
    83          WRITE(charout, FMT="('zdf ')") ;  CALL prt_ctl_trc_info(charout) 
    84                                            CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     68         WRITE(charout, FMT="('zdf ')") 
     69         CALL prt_ctl_trc_info(charout) 
     70         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    8571      END IF 
    8672      ! 
     
    8874      ! 
    8975   END SUBROUTINE trc_zdf 
    90  
    91  
    92    SUBROUTINE trc_zdf_ini 
    93       !!---------------------------------------------------------------------- 
    94       !!                 ***  ROUTINE trc_zdf_ini  *** 
    95       !! 
    96       !! ** Purpose :   Choose the vertical mixing scheme 
    97       !! 
    98       !! ** Method  :   Set nzdf from ln_zdfexp 
    99       !!      nzdf = 0   explicit (time-splitting) scheme (ln_trczdf_exp=T) 
    100       !!           = 1   implicit (euler backward) scheme (ln_trczdf_exp=F) 
    101       !!      NB: The implicit scheme is required when using :  
    102       !!             - rotated lateral mixing operator 
    103       !!             - TKE, GLS vertical mixing scheme 
    104       !!---------------------------------------------------------------------- 
    105       INTEGER ::  ios                 ! Local integer output status for namelist read 
    106       !! 
    107       NAMELIST/namtrc_zdf/ ln_trczdf_exp  , nn_trczdf_exp 
    108       !!---------------------------------------------------------------------- 
    109       ! 
    110       REWIND( numnat_ref )             ! namtrc_zdf in reference namelist  
    111       READ  ( numnat_ref, namtrc_zdf, IOSTAT = ios, ERR = 905) 
    112 905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in reference namelist', lwp ) 
    113       ! 
    114       REWIND( numnat_cfg )             ! namtrc_zdf in configuration namelist  
    115       READ  ( numnat_cfg, namtrc_zdf, IOSTAT = ios, ERR = 906 ) 
    116 906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in configuration namelist', lwp ) 
    117       IF(lwm) WRITE ( numont, namtrc_zdf ) 
    118       ! 
    119       IF(lwp) THEN                     ! Control print 
    120          WRITE(numout,*) 
    121          WRITE(numout,*) '   Namelist namtrc_zdf : set vertical diffusion  parameters' 
    122          WRITE(numout,*) '      time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp 
    123          WRITE(numout,*) '      number of time step              nn_trczdf_exp = ', nn_trczdf_exp 
    124       ENDIF 
    125  
    126       !                                ! Define the vertical tracer physics scheme 
    127       IF( ln_trczdf_exp ) THEN   ;   nzdf = 0     ! explicit scheme 
    128       ELSE                       ;   nzdf = 1     ! implicit scheme 
    129       ENDIF 
    130  
    131       !                                ! Force implicit schemes 
    132       IF( ln_trcldf_iso              )   nzdf = 1      ! iso-neutral lateral physics 
    133       IF( ln_trcldf_hor .AND. ln_sco )   nzdf = 1      ! horizontal lateral physics in s-coordinate 
    134 #if defined key_zdftke || defined key_zdfgls  
    135                                          nzdf = 1      ! TKE or GLS physics        
    136 #endif 
    137       IF( ln_trczdf_exp .AND. nzdf == 1 )  &  
    138          CALL ctl_stop( 'trc_zdf : If using the rotated lateral mixing operator or TKE, GLS vertical scheme ', & 
    139             &           '          the implicit scheme is required, set ln_trczdf_exp = .false.' ) 
    140  
    141       IF(lwp) THEN 
    142          WRITE(numout,*) 
    143          WRITE(numout,*) 'trc:zdf_ctl : vertical passive tracer physics scheme' 
    144          WRITE(numout,*) '~~~~~~~~~~~' 
    145          IF( nzdf ==  0 )   WRITE(numout,*) '              Explicit time-splitting scheme' 
    146          IF( nzdf ==  1 )   WRITE(numout,*) '              Implicit (euler backward) scheme' 
    147       ENDIF 
    148       ! 
    149    END SUBROUTINE trc_zdf_ini 
    15076    
    15177#else 
  • branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/TOP_SRC/TRP/trdmxl_trc.F90

    r7646 r8215  
    2020   USE dom_oce           ! domain definition 
    2121   USE zdfmxl  , ONLY : nmln ! number of level in the mixed layer 
    22    USE zdf_oce , ONLY : avt  ! vert. diffusivity coef. at w-point for temp   
    23 # if defined key_zdfddm    
    24    USE zdfddm  , ONLY : avs  ! salinity vertical diffusivity coeff. at w-point 
    25 # endif 
     22   USE zdf_oce , ONLY : avs  ! vert. diffusivity coef. at w-point for temp   
    2623   USE trdtrc_oce    ! definition of main arrays used for trends computations 
    2724   USE in_out_manager    ! I/O manager 
     
    5451   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  ztmltrd2   ! 
    5552 
    56    !! * Substitutions 
    57 #  include "zdfddm_substitute.h90" 
    5853   !!---------------------------------------------------------------------- 
    5954   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     
    275270      IF( ln_trcldf_iso ) THEN 
    276271         ! 
    277          DO jj = 1,jpj 
    278             DO ji = 1,jpi 
    279                ik = nmld_trc(ji,jj) 
    280                zavt = fsavs(ji,jj,ik) 
    281                DO jn = 1, jptra 
     272         DO jn = 1, jptra 
     273            DO jj = 1, jpj 
     274               DO ji = 1, jpi 
     275                  ik = nmld_trc(ji,jj) 
    282276                  IF( ln_trdtrc(jn) )    & 
    283                   tmltrd_trc(ji,jj,jpmxl_trc_zdf,jn) = - zavt / e3w_n(ji,jj,ik) * tmask(ji,jj,ik)  & 
     277                  tmltrd_trc(ji,jj,jpmxl_trc_zdf,jn) = - avs(ji,jj,ik) / e3w_n(ji,jj,ik) * tmask(ji,jj,ik)  & 
    284278                       &                    * ( trn(ji,jj,ik-1,jn) - trn(ji,jj,ik,jn) )            & 
    285279                       &                    / MAX( 1., rmld_trc(ji,jj) ) * tmask(ji,jj,1) 
Note: See TracChangeset for help on using the changeset viewer.