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 13463 for NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/TRD/trdmxl.F90 – NEMO

Ignore:
Timestamp:
2020-09-14T17:40:34+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2195:update to trunk 13461

Location:
NEMO/branches/2019/dev_r11351_fldread_with_XIOS
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@13382        sette 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/TRD/trdmxl.F90

    r10425 r13463  
    6868   INTEGER ::   ionce, icount                    
    6969 
     70   !! * Substitutions 
     71#  include "do_loop_substitute.h90" 
     72#  include "domzgr_substitute.h90" 
    7073   !!---------------------------------------------------------------------- 
    7174   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    8689 
    8790 
    88    SUBROUTINE trd_tra_mxl( ptrdx, ptrdy, ktrd, kt, p2dt, kmxln ) 
     91   SUBROUTINE trd_tra_mxl( ptrdx, ptrdy, ktrd, kt, p2dt, kmxln, Kmm ) 
    8992      !!---------------------------------------------------------------------- 
    9093      !!                  ***  ROUTINE trd_tra_mng  *** 
     
    98101      INTEGER                   , INTENT(in   ) ::   ktrd    ! tracer trend index 
    99102      INTEGER                   , INTENT(in   ) ::   kt      ! time step index 
     103      INTEGER                   , INTENT(in   ) ::   Kmm     ! time level index 
    100104      REAL(wp)                  , INTENT(in   ) ::   p2dt    ! time step  [s] 
    101105      REAL(wp), DIMENSION(:,:)  , INTENT(in   ) ::   kmxln   ! number of t-box for the vertical average  
     
    116120         ! 
    117121         wkx(:,:,:) = 0._wp         !==  now ML weights for vertical averaging  ==! 
    118          DO jk = 1, jpktrd               ! initialize wkx with vertical scale factor in mixed-layer 
    119             DO jj = 1,jpj 
    120                DO ji = 1,jpi 
    121                   IF( jk - kmxln(ji,jj) < 0 )   wkx(ji,jj,jk) = e3t_n(ji,jj,jk) * tmask(ji,jj,jk) 
    122                END DO 
    123             END DO 
    124          END DO 
     122         DO_3D( 1, 1, 1, 1, 1, jpktrd ) 
     123            IF( jk - kmxln(ji,jj) < 0 )   THEN 
     124               wkx(ji,jj,jk) = e3t(ji,jj,jk,Kmm) * tmask(ji,jj,jk) 
     125            ENDIF 
     126         END_3D 
    125127         hmxl(:,:) = 0._wp               ! NOW mixed-layer depth 
    126128         DO jk = 1, jpktrd 
     
    136138         tml(:,:) = 0._wp   ;   sml(:,:) = 0._wp 
    137139         DO jk = 1, jpktrd 
    138             tml(:,:) = tml(:,:) + wkx(:,:,jk) * tsn(:,:,jk,jp_tem) 
    139             sml(:,:) = sml(:,:) + wkx(:,:,jk) * tsn(:,:,jk,jp_sal) 
     140            tml(:,:) = tml(:,:) + wkx(:,:,jk) * ts(:,:,jk,jp_tem,Kmm) 
     141            sml(:,:) = sml(:,:) + wkx(:,:,jk) * ts(:,:,jk,jp_sal,Kmm) 
    140142         END DO 
    141143         ! 
     
    152154!!gm to be put juste before the output ! 
    153155!      ! Lateral boundary conditions 
    154 !      CALL lbc_lnk_multi( 'trdmxl', tmltrd(:,:,jl), 'T', 1. , smltrd(:,:,jl), 'T', 1. ) 
     156!      CALL lbc_lnk_multi( 'trdmxl', tmltrd(:,:,jl), 'T', 1.0_wp , smltrd(:,:,jl), 'T', 1.0_wp ) 
    155157!!gm end 
    156158 
     
    371373         hmxlbn(:,:) = hmxl(:,:) 
    372374 
    373          IF( ln_ctl ) THEN 
     375         IF( sn_cfctl%l_prtctl ) THEN 
    374376            WRITE(numout,*) '             we reach kt == nit000 + 1 = ', nit000+1 
    375377            CALL prt_ctl(tab2d_1=tmlbb   , clinfo1=' tmlbb   -   : ', mask1=tmask) 
     
    380382      END IF 
    381383 
    382       IF( ( ln_rstart ) .AND. ( kt == nit000 ) .AND. ( ln_ctl ) ) THEN 
     384      IF( ( ln_rstart ) .AND. ( kt == nit000 ) .AND. sn_cfctl%l_prtctl ) THEN 
    383385         IF( ln_trdmxl_instant ) THEN 
    384386            WRITE(numout,*) '             restart from kt == nit000 = ', nit000 
     
    470472         !-- Lateral boundary conditions 
    471473         !         ... temperature ...                    ... salinity ... 
    472          CALL lbc_lnk_multi( 'trdmxl', ztmltot , 'T', 1., zsmltot , 'T', 1., & 
    473                   &          ztmlres , 'T', 1., zsmlres , 'T', 1., & 
    474                   &          ztmlatf , 'T', 1., zsmlatf , 'T', 1. ) 
     474         CALL lbc_lnk_multi( 'trdmxl', ztmltot , 'T', 1.0_wp, zsmltot , 'T', 1.0_wp, & 
     475                  &          ztmlres , 'T', 1.0_wp, zsmlres , 'T', 1.0_wp, & 
     476                  &          ztmlatf , 'T', 1.0_wp, zsmlatf , 'T', 1.0_wp ) 
    475477 
    476478 
     
    521523         !-- Lateral boundary conditions 
    522524         !         ... temperature ...                    ... salinity ... 
    523          CALL lbc_lnk_multi( 'trdmxl', ztmltot2, 'T', 1., zsmltot2, 'T', 1., & 
    524                   &          ztmlres2, 'T', 1., zsmlres2, 'T', 1. ) 
    525          ! 
    526          CALL lbc_lnk_multi( 'trdmxl', ztmltrd2(:,:,:), 'T', 1., zsmltrd2(:,:,:), 'T', 1. ) ! /  in the NetCDF trends file 
     525         CALL lbc_lnk_multi( 'trdmxl', ztmltot2, 'T', 1.0_wp, zsmltot2, 'T', 1.0_wp, & 
     526                  &          ztmlres2, 'T', 1.0_wp, zsmlres2, 'T', 1.0_wp ) 
     527         ! 
     528         CALL lbc_lnk_multi( 'trdmxl', ztmltrd2(:,:,:), 'T', 1.0_wp, zsmltrd2(:,:,:), 'T', 1.0_wp ) ! /  in the NetCDF trends file 
    527529          
    528530         ! III.3 Time evolution array swap 
     
    548550         hmxlbn         (:,:)   = hmxl    (:,:) 
    549551          
    550          IF( ln_ctl ) THEN 
     552         IF( sn_cfctl%l_prtctl ) THEN 
    551553            IF( ln_trdmxl_instant ) THEN 
    552554               CALL prt_ctl(tab2d_1=tmlbb   , clinfo1=' tmlbb   -   : ', mask1=tmask) 
     
    732734      !!---------------------------------------------------------------------- 
    733735      ! 
    734       REWIND( numnam_ref )              ! Namelist namtrd_mxl in reference namelist : mixed layer trends diagnostic 
    735736      READ  ( numnam_ref, namtrd_mxl, IOSTAT = ios, ERR = 901 ) 
    736 901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrd_mxl in reference namelist', lwp ) 
    737  
    738       REWIND( numnam_cfg )              ! Namelist namtrd_mxl in configuration namelist : mixed layer trends diagnostic 
     737901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrd_mxl in reference namelist' ) 
     738 
    739739      READ  ( numnam_cfg, namtrd_mxl, IOSTAT = ios, ERR = 902 ) 
    740 902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrd_mxl in configuration namelist', lwp ) 
     740902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrd_mxl in configuration namelist' ) 
    741741      IF(lwm) WRITE( numond, namtrd_mxl ) 
    742742      ! 
     
    764764 
    765765      IF( MOD( nitend, nn_trd ) /= 0 ) THEN 
    766          WRITE(numout,cform_err) 
    767          WRITE(numout,*) '                Your nitend parameter, nitend = ', nitend 
    768          WRITE(numout,*) '                is no multiple of the trends diagnostics frequency        ' 
    769          WRITE(numout,*) '                          you defined, nn_trd   = ', nn_trd 
    770          WRITE(numout,*) '                This will not allow you to restart from this simulation.  ' 
    771          WRITE(numout,*) '                You should reconsider this choice.                        '  
    772          WRITE(numout,*)  
    773          WRITE(numout,*) '                N.B. the nitend parameter is also constrained to be a     ' 
    774          WRITE(numout,*) '                     multiple of the nn_fsbc parameter ' 
    775          CALL ctl_stop( 'trd_mxl_init: see comment just above' ) 
     766         WRITE(ctmp1,*) '                Your nitend parameter, nitend = ', nitend 
     767         WRITE(ctmp2,*) '                is no multiple of the trends diagnostics frequency        ' 
     768         WRITE(ctmp3,*) '                          you defined, nn_trd   = ', nn_trd 
     769         WRITE(ctmp4,*) '                This will not allow you to restart from this simulation.  ' 
     770         WRITE(ctmp5,*) '                You should reconsider this choice.                        '  
     771         WRITE(ctmp6,*)  
     772         WRITE(ctmp7,*) '                N.B. the nitend parameter is also constrained to be a     ' 
     773         WRITE(ctmp8,*) '                     multiple of the nn_fsbc parameter ' 
     774         CALL ctl_stop( ctmp1, ctmp2, ctmp3, ctmp4, ctmp5, ctmp6, ctmp7, ctmp8 ) 
    776775      END IF 
    777776 
Note: See TracChangeset for help on using the changeset viewer.