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 15373 – NEMO

Changeset 15373


Ignore:
Timestamp:
2021-10-14T19:01:57+02:00 (3 years ago)
Author:
techene
Message:

#2715 RK3: adapt trc surface boundary management

Location:
NEMO/branches/2021/dev_r14318_RK3_stage1/src
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE/stprk3_stg.F90

    r15321 r15373  
    2727   USE trcsms         ! passive tracers source and sink 
    2828   USE trctrp         ! passive tracers transport 
     29   USE trcsbc         ! passive tracers surface boundary condition !!st WARNING USELESS TO BE REMOVED 
    2930   USE trcbdy         ! passive tracers transport open boundary 
    3031   USE trcstp_rk3 
     
    218219      !                                         !==  advection of passive tracers  ==! 
    219220      rDt_trc = rDt 
    220       CALL trc_adv( kstp, Kbb, Kmm, tr, Krhs, zaU, zaV, ww )      ! horizontal & vertical advection 
     221!!st 
     222      CALL trc_sbc_RK3( kstp,      Kmm, tr, Krhs, kstg )              ! surface boundary condition 
     223      ! 
     224      CALL trc_adv    ( kstp, Kbb, Kmm, tr, Krhs, zaU, zaV, ww )      ! horizontal & vertical advection 
    221225      ! 
    222226      ! 
     
    357361                            CALL tra_zdf( kstp, Kbb, Kmm, Krhs, ts    , Kaa  )  ! vertical mixing and after tracer fields 
    358362         IF( ln_zdfnpc  )   CALL tra_npc( kstp,      Kmm, Krhs, ts    , Kaa  )  ! update after fields by non-penetrative convection 
    359          !          
     363         ! 
    360364      END SELECT       
    361365      !                                         !==  correction of the barotropic (all stages)  ==!    at Kaa = N+1/3, N+1/2 or N+1 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/TRP/trcatf.F90

    r14800 r15373  
    2121   !!            4.1  !  2019-08  (A. Coward, D. Storkey) rename trcnxt.F90 -> trcatf.F90. Now only does time filtering. 
    2222   !!---------------------------------------------------------------------- 
    23 #if defined key_top 
     23#if defined key_top   &&   ! defined key_RK3 
    2424   !!---------------------------------------------------------------------- 
    2525   !!   'key_top'                                                TOP models 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/TRP/trcsbc.F90

    r14215 r15373  
    1717   !!---------------------------------------------------------------------- 
    1818   USE par_trc        ! need jptra, number of passive tracers 
    19    USE oce_trc         ! ocean dynamics and active tracers variables 
    20    USE trc             ! ocean  passive tracers variables 
    21    USE prtctl          ! Print control for debbuging 
     19   USE oce_trc        ! ocean dynamics and active tracers variables 
     20   USE trc            ! ocean  passive tracers variables 
     21   USE prtctl         ! Print control for debbuging 
    2222   USE iom 
    2323   USE trd_oce 
     
    2727   PRIVATE 
    2828 
    29    PUBLIC   trc_sbc   ! routine called by step.F90 
     29   PUBLIC   trc_sbc       ! routine called by trctrp.F90 
     30   PUBLIC   trc_sbc_RK3   ! routine called by stprk3_stg.F90 
    3031 
    3132   !! * Substitutions 
     
    8485         IF(lwp) WRITE(numout,*) '~~~~~~~ ' 
    8586         ! 
     87#if ! defined key_RK3 
    8688         IF( ln_rsttr .AND. .NOT.ln_top_euler .AND.   &                     ! Restart: read in restart  file 
    8789            iom_varid( numrtr, 'sbc_'//TRIM(ctrcnm(1))//'_b', ldstop = .FALSE. ) > 0 ) THEN 
     
    104106         ENDIF 
    105107         ! 
     108#endif 
    106109      ENDIF 
    107110 
     
    139142         DO jn = 1, jptra 
    140143            DO_2D( 0, 0, 0, 1 ) 
    141                zse3t = 1. / e3t(ji,jj,1,Kmm) 
    142144               ! tracer flux at the ice/ocean interface (tracer/m2/s) 
    143145               zftra = - trc_i(ji,jj,jn) * fmmflx(ji,jj) ! uptake of tracer in the sea ice 
     
    163165         ! 
    164166         DO_2D( 0, 0, 0, 1 ) 
     167#if defined key_RK3 
     168            zse3t = 1._wp / e3t(ji,jj,1,Kmm) 
     169            ptr(ji,jj,1,jn,Krhs) = ptr(ji,jj,1,jn,Krhs) + sbc_trc(ji,jj,jn) * zse3t 
     170#else 
    165171            zse3t = zfact / e3t(ji,jj,1,Kmm) 
    166172            ptr(ji,jj,1,jn,Krhs) = ptr(ji,jj,1,jn,Krhs) + ( sbc_trc_b(ji,jj,jn) + sbc_trc(ji,jj,jn) ) * zse3t 
     173#endif 
    167174         END_2D 
    168175         ! 
     
    175182      !                                                          ! =========== 
    176183      ! 
     184#if ! defined key_RK3 
    177185      !                                           Write in the tracer restar  file 
    178186      !                                          ******************************* 
     
    186194         END DO 
    187195      ENDIF 
     196#endif 
    188197      ! 
    189198      IF( sn_cfctl%l_prttrc )   THEN 
     
    196205      ! 
    197206   END SUBROUTINE trc_sbc 
     207 
     208!!st 
     209   SUBROUTINE trc_sbc_RK3 ( kt, Kmm, ptr, Krhs, kstg ) 
     210      !!---------------------------------------------------------------------- 
     211      !!                  ***  ROUTINE trc_sbc_RK3  *** 
     212      !!                    
     213      !! ** Purpose :   Compute the tracer surface boundary condition trend of 
     214      !!      (concentration/dilution effect) and add it to the general  
     215      !!       trend of tracer equations. 
     216      !! 
     217      !! ** Method : 
     218      !!      * concentration/dilution effect: 
     219      !!            The surface freshwater flux modify the ocean volume 
     220      !!         and thus the concentration of a tracer as : 
     221      !!            tr(Krhs) = tr(Krhs) + emp * tr(Kmm) / e3t_   for k=1 
     222      !!         where emp, the surface freshwater budget (evaporation minus 
     223      !!         precipitation ) given in kg/m2/s is divided 
     224      !!         by 1035 kg/m3 (density of ocean water) to obtain m/s. 
     225      !! 
     226      !! ** Action  : - Update the 1st level of tr(:,:,:,:,Krhs) with the trend associated 
     227      !!                with the tracer surface boundary condition  
     228      !! 
     229      !!---------------------------------------------------------------------- 
     230      INTEGER                                   , INTENT(in   ) ::   kt, Kmm, Krhs   ! ocean time-step and time-level indices 
     231      INTEGER                                   , INTENT(in   ) ::   kstg            ! RK3 stage index 
     232      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) ::   ptr       ! passive tracers and RHS of tracer equation 
     233      ! 
     234      INTEGER  ::   ji, jj, jn                      ! dummy loop indices 
     235      REAL(wp) ::   zse3t, zrtrn, zfact     ! local scalars 
     236      REAL(wp) ::   zftra, zdtra, ztfx, ztra   !   -      - 
     237      CHARACTER (len=22) :: charout 
     238      REAL(wp), DIMENSION(jpi,jpj)   ::   zmfx 
     239      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrtrd 
     240      !!--------------------------------------------------------------------- 
     241      ! 
     242      IF( ln_timing )   CALL timing_start('trc_sbc_RK3') 
     243      ! 
     244      ! Allocate temporary workspace 
     245      IF( l_trdtrc )  ALLOCATE( ztrtrd(jpi,jpj,jpk) ) 
     246      ! 
     247      IF( kt == nittrc000 ) THEN 
     248         IF(lwp) WRITE(numout,*) 
     249         IF(lwp) WRITE(numout,*) 'trc_sbc_RK3 : Passive tracers surface boundary condition' 
     250         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~ ' 
     251      ENDIF 
     252!!st: not sure of the way to deal about this 
     253      SELECT CASE( kstg ) 
     254      ! 
     255      CASE( 1 , 2 )                       !=  stage 1 and 2  =!   only in non linear ssh 
     256         ! 
     257         IF( .NOT.ln_linssh ) THEN           !* only passive tracer fluxes associated with mass fluxes 
     258            ! 
     259            SELECT CASE ( nn_ice_tr ) 
     260               ! 
     261            CASE ( -1 , 0 , 1 )                      ! no passive tracer concentration modification due to ssh variation 
     262               ! 
     263!!st emp includes fmm see iceupdate.F90 
     264               DO jn = 1, jptra 
     265                  DO_2D( 0, 0, 0, 1 ) 
     266                     sbc_trc(ji,jj,jn) =  - emp(ji,jj) * ptr(ji,jj,1,jn,Kmm) * r1_rho0 
     267                  END_2D 
     268               END DO 
     269               ! 
     270            END SELECT 
     271            ! 
     272         ENDIF 
     273         ! 
     274      CASE( 3 ) 
     275!!st copy of existing code 
     276         ! 
     277         IF( .NOT.ln_linssh ) THEN    !!st concentration/dilution effect due to volume variation  
     278            SELECT CASE ( nn_ice_tr ) 
     279            ! 
     280            CASE ( 0 )  ! Same concentration in sea ice and in the ocean 
     281               ! 
     282               DO jn = 1, jptra 
     283                  DO_2D( 0, 0, 0, 1 ) 
     284                     sbc_trc(ji,jj,jn) =  - fmmflx(ji,jj) * r1_rho0 * ptr(ji,jj,1,jn,Kmm) 
     285                  END_2D 
     286               END DO 
     287               ! 
     288            CASE ( 1 )  ! Specific treatment of sea ice fluxes with an imposed concentration in sea ice  
     289               ! 
     290               DO jn = 1, jptra 
     291                  DO_2D( 0, 0, 0, 1 ) 
     292                  ! tracer flux at the ice/ocean interface (tracer/m2/s) 
     293                  zftra = - trc_i(ji,jj,jn) * fmmflx(ji,jj) ! uptake of tracer in the sea ice 
     294                  !                                         ! only used in the levitating sea ice case 
     295                  ! tracer flux only       : add concentration dilution term in net tracer flux, no F-M in volume flux 
     296                  ! tracer and mass fluxes : no concentration dilution term in net tracer flux, F-M term in volume flux 
     297                  ztfx  = zftra                        ! net tracer flux 
     298                  ! 
     299                  zdtra = r1_rho0 * ( ztfx -  fmmflx(ji,jj) * ptr(ji,jj,1,jn,Kmm) )  
     300                  IF ( zdtra < 0. ) THEN 
     301                     zdtra  = MAX(zdtra, -ptr(ji,jj,1,jn,Kmm) * e3t(ji,jj,1,Kmm) / rDt_trc )   ! avoid negative concentrations to arise 
     302                  ENDIF 
     303                  sbc_trc(ji,jj,jn) =  zdtra  
     304                  END_2D 
     305               END DO 
     306               ! 
     307            END SELECT 
     308         ELSE                         !linear ssh !!st need to mimic concentration/dilution effect since no volume variation  
     309            SELECT CASE ( nn_ice_tr ) 
     310            ! 
     311            CASE ( -1 ) ! No tracers in sea ice (null concentration in sea ice) 
     312               ! 
     313               DO jn = 1, jptra 
     314                  DO_2D( 0, 0, 0, 1 ) 
     315                  sbc_trc(ji,jj,jn) = emp(ji,jj) * r1_rho0 * ptr(ji,jj,1,jn,Kmm) 
     316                  END_2D 
     317               END DO 
     318               ! 
     319            CASE ( 0 )  ! Same concentration in sea ice and in the ocean 
     320               ! 
     321               DO jn = 1, jptra 
     322                  DO_2D( 0, 0, 0, 1 ) 
     323                     sbc_trc(ji,jj,jn) = ( emp(ji,jj) - fmmflx(ji,jj) ) * r1_rho0 * ptr(ji,jj,1,jn,Kmm) 
     324                  END_2D 
     325               END DO 
     326               ! 
     327            CASE ( 1 )  ! Specific treatment of sea ice fluxes with an imposed concentration in sea ice  
     328               ! 
     329               DO jn = 1, jptra 
     330                  DO_2D( 0, 0, 0, 1 ) 
     331                  ! tracer flux at the ice/ocean interface (tracer/m2/s) 
     332                  zftra = - trc_i(ji,jj,jn) * fmmflx(ji,jj) ! uptake of tracer in the sea ice 
     333                  !                                         ! only used in the levitating sea ice case 
     334                  ! tracer flux only       : add concentration dilution term in net tracer flux, no F-M in volume flux 
     335                  ! tracer and mass fluxes : no concentration dilution term in net tracer flux, F-M term in volume flux 
     336                  ztfx  = zftra                        ! net tracer flux 
     337                  ! 
     338                  zdtra = r1_rho0 * ( ztfx +  ( emp(ji,jj) - fmmflx(ji,jj) ) * ptr(ji,jj,1,jn,Kmm) )  
     339                  IF ( zdtra < 0. ) THEN 
     340                     zdtra  = MAX(zdtra, -ptr(ji,jj,1,jn,Kmm) * e3t(ji,jj,1,Kmm) / rDt_trc )   ! avoid negative concentrations to arise 
     341                  ENDIF 
     342                  sbc_trc(ji,jj,jn) =  zdtra  
     343                  END_2D 
     344               END DO 
     345               ! 
     346            END SELECT 
     347            ! 
     348         ENDIF 
     349         ! 
     350         ! 
     351         ! 
     352      END SELECT 
     353      ! 
     354      CALL lbc_lnk( 'trcsbc', sbc_trc(:,:,:), 'T', 1.0_wp ) 
     355      !                                       Concentration dilution effect on tracers due to evaporation & precipitation  
     356      DO jn = 1, jptra 
     357         ! 
     358         IF( l_trdtrc )   ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs)  ! save trends 
     359         ! 
     360         IF(lwp) WRITE(numout,*) 
     361         IF(lwp) WRITE(numout,*) 'trc_sbc_RK3 : Runge Kutta 3rd order at stage ', kstg, jn 
     362         IF(lwp) WRITE(numout,*) 'emp', MAXVAL(emp(:,:)) 
     363         IF(lwp) WRITE(numout,*) 'sbc_trc', MAXVAL(sbc_trc(:,:,jn)) 
     364         IF(lwp) WRITE(numout,*) 
     365         DO_2D( 0, 0, 0, 1 ) 
     366            zse3t = 1._wp / e3t(ji,jj,1,Kmm) 
     367            ptr(ji,jj,1,jn,Krhs) = ptr(ji,jj,1,jn,Krhs) +  sbc_trc(ji,jj,jn) * zse3t 
     368         END_2D 
     369         ! 
     370         IF( l_trdtrc ) THEN 
     371            ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs) - ztrtrd(:,:,:) 
     372            CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_nsr, ztrtrd ) 
     373         END IF 
     374         ! 
     375      END DO 
     376      ! 
     377      IF( sn_cfctl%l_prttrc )   THEN 
     378         WRITE(charout, FMT="('sbc ')") ;  CALL prt_ctl_info( charout, cdcomp = 'top' ) 
     379                                           CALL prt_ctl( tab4d_1=ptr(:,:,:,:,Krhs), mask1=tmask, clinfo=ctrcnm, clinfo3='trd' ) 
     380      ENDIF 
     381      ! 
     382      IF( l_trdtrc )  DEALLOCATE( ztrtrd ) 
     383      ! 
     384      IF( ln_timing )   CALL timing_stop('trc_sbc_RK3') 
     385      ! 
     386   END SUBROUTINE trc_sbc_RK3 
     387!!st 
    198388 
    199389#else 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/TRP/trctrp.F90

    r15321 r15373  
    7373         ENDIF 
    7474         ! 
     75#if ! defined key_RK3                                 
    7576                                CALL trc_sbc    ( kt,      Kmm, tr, Krhs )      ! surface boundary condition 
     77#endif 
    7678         IF( ln_trcbc .AND. lltrcbc .AND. kt /= nit000 )  & 
    7779                                CALL trc_bc     ( kt,      Kmm, tr, Krhs )      ! tracers: surface and lateral Boundary Conditions  
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/trcsms.F90

    r13286 r15373  
    5959         WRITE(charout, FMT="('sms ')") 
    6060         CALL prt_ctl_info( charout, cdcomp = 'top' ) 
     61#if defined key_RK3 
     62         CALL prt_ctl( tab4d_1=tr(:,:,:,:,Krhs), mask1=tmask, clinfo=ctrcnm ) 
     63#else 
    6164         CALL prt_ctl( tab4d_1=tr(:,:,:,:,Kmm), mask1=tmask, clinfo=ctrcnm ) 
     65#endif 
    6266      ENDIF 
    6367      ! 
Note: See TracChangeset for help on using the changeset viewer.