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

Changeset 15321


Ignore:
Timestamp:
2021-10-04T12:24:15+02:00 (3 years ago)
Author:
techene
Message:

#2605 #2715 some cleanning

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

Legend:

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

    r15281 r15321  
    2424# if defined key_top 
    2525   USE trc            ! ocean passive tracers variables 
    26    USE trcadv         ! advection                           (trc_adv routine) 
    27    USE trcsms         ! source and sink 
    28    USE trctrp         ! transport 
    29    USE trcbdy 
     26   USE trcadv         ! passive tracers advection      (trc_adv routine) 
     27   USE trcsms         ! passive tracers source and sink 
     28   USE trctrp         ! passive tracers transport 
     29   USE trcbdy         ! passive tracers transport open boundary 
    3030   USE trcstp_rk3 
    3131# endif 
     
    204204 
    205205# if defined key_top 
     206      ! 
    206207      !                       !==  Passive Tracer  ==! 
    207208      ! 
     
    237238      CASE ( 3 )           !==  Stage 3  ==!   add all RHS terms but advection (=> Kbb only) 
    238239         !                 !---------------! 
    239          CALL trc_sms( kstp, Kbb, Kbb, Krhs      )       ! tracers: sinks and sources 
    240          CALL trc_trp( kstp, Kbb, Kmm, Krhs, Kaa )       ! transport of passive tracers (without advection) 
    241          ! 
    242 !!st a mettre dans trp  
    243 !!st# if defined key_agrif 
    244 !!st         CALL Agrif_trc( kstp )                ! AGRIF zoom boundaries 
    245 !!st# endif 
    246 !!st         ! Update after tracer on domain lateral boundaries 
    247 !!st         CALL lbc_lnk( 'stprk3_stg', tr(:,:,:,:,Kaa), 'T', 1._wp )    
    248 !!st         ! 
    249 !!st         IF( ln_bdy )  CALL trc_bdy( kstp, Kbb, Kmm, Kaa ) 
    250          ! 
    251          CALL trc_stp_end( kstp, Kbb, Kmm, Kaa ) 
     240         CALL trc_sms    ( kstp, Kbb, Kbb, Krhs      )       ! tracers: sinks and sources 
     241         CALL trc_trp    ( kstp, Kbb, Kmm, Krhs, Kaa )       ! transport of passive tracers (without advection) 
     242         ! 
     243         ! 
     244         CALL trc_stp_end( kstp, Kbb, Kmm,       Kaa ) 
    252245         ! 
    253246      END SELECT 
     
    271264                        CALL tra_sbc_RK3( kstp,      Kmm, ts, Krhs, kstg )   ! surface boundary condition 
    272265 
    273       IF( ln_isf )      CALL tra_isf( kstp,      Kmm, ts, Krhs )   ! ice shelf heat flux 
    274       IF( ln_traqsr )   CALL tra_qsr( kstp,      Kmm, ts, Krhs )   ! penetrative solar radiation qsr 
     266      IF( ln_isf )      CALL tra_isf    ( kstp,      Kmm, ts, Krhs )   ! ice shelf heat flux 
     267      IF( ln_traqsr )   CALL tra_qsr    ( kstp,      Kmm, ts, Krhs )   ! penetrative solar radiation qsr 
    275268!!gm 
    276269 
     
    330323         !                                      !==  complete the momentum RHS ==!   except ZDF (implicit) 
    331324         !                                                   ! lateral mixing                    ==> RHS 
    332                             CALL dyn_ldf( kstp, Kbb, Kmm      , uu, vv, Krhs ) 
     325                            CALL dyn_ldf( kstp, Kbb, Kmm, uu, vv, Krhs ) 
    333326         !                                                   ! OSMOSIS non-local velocity fluxes ==> RHS 
    334          IF( ln_zdfosm  )   CALL dyn_osm( kstp,      Kmm      , uu, vv, Krhs ) 
     327         IF( ln_zdfosm  )   CALL dyn_osm( kstp,      Kmm, uu, vv, Krhs ) 
    335328         !                     
    336329         IF( ln_bdy     ) THEN                               ! bdy damping trends     ==> RHS 
     
    340333 
    341334# if defined key_agrif 
    342          IF(.NOT. Agrif_Root() ) THEN     ! AGRIF:   sponge ==> momentum and tracer RHS 
     335         IF(.NOT. Agrif_Root() ) THEN                        ! AGRIF:   sponge ==> momentum and tracer RHS 
    343336            CALL Agrif_Sponge_dyn 
    344337            CALL Agrif_Sponge_tra 
     
    349342         ! 
    350343                            CALL tra_ldf( kstp, Kbb, Kmm, ts, Krhs )  ! lateral mixing 
    351 !!gm ====>>>>   already called in stage 1, 2 and 3 case 
    352 !!st                            CALL tra_sbc( kstp,      Kmm, ts, Krhs )   ! surface boundary condition 
    353 !!st         IF( ln_isf )       CALL tra_isf( kstp,      Kmm, ts, Krhs )   ! ice shelf heat flux 
    354 !!gm 
    355          ! 
    356 !!st         IF( ln_traqsr  )   CALL tra_qsr( kstp,      Kmm, ts, Krhs )  ! penetrative solar radiation qsr 
    357344         IF( ln_trabbc  )   CALL tra_bbc( kstp,      Kmm, ts, Krhs )  ! bottom heat flux 
    358345         IF( ln_trabbl  )   CALL tra_bbl( kstp, Kbb, Kmm, ts, Krhs )  ! advective (and/or diffusive) bottom boundary layer scheme 
     
    364351            IF( lrst_oce )  CALL osm_rst( kstp,      Kmm, 'WRITE'  )  ! write OSMOSIS outputs + ww (so must do here) to restarts 
    365352         ENDIF 
    366  
    367353         ! 
    368354         !                                      !==  DYN & TRA time integration + ZDF  ==!   ∆t = rDt 
     
    370356                            CALL dyn_zdf( kstp, Kbb, Kmm, Krhs, uu, vv, Kaa  )  ! vertical diffusion and time integration  
    371357                            CALL tra_zdf( kstp, Kbb, Kmm, Krhs, ts    , Kaa  )  ! vertical mixing and after tracer fields 
    372          ! 
    373358         IF( ln_zdfnpc  )   CALL tra_npc( kstp,      Kmm, Krhs, ts    , Kaa  )  ! update after fields by non-penetrative convection 
    374359         !          
     
    378363      zub(A2D(0)) = uu_b(A2D(0),Kaa) - SUM( e3u_0(A2D(0),:)*uu(A2D(0),:,Kaa), 3 ) * r1_hu_0(A2D(0)) 
    379364      zvb(A2D(0)) = vv_b(A2D(0),Kaa) - SUM( e3v_0(A2D(0),:)*vv(A2D(0),:,Kaa), 3 ) * r1_hv_0(A2D(0)) 
    380  
    381 !!st      zub(:,:) = uu_b(:,:,Kaa) - SUM( e3u_0(:,:,:)*uu(:,:,:,Kaa), 3 ) * r1_hu_0(:,:) 
    382 !!st      zvb(:,:) = vv_b(:,:,Kaa) - SUM( e3v_0(:,:,:)*vv(:,:,:,Kaa), 3 ) * r1_hv_0(:,:) 
    383  
     365      ! 
    384366      DO jk = 1, jpkm1                                            ! corrected horizontal velocity 
    385367         uu(:,:,jk,Kaa) = uu(:,:,jk,Kaa) + zub(:,:)*umask(:,:,jk) 
    386368         vv(:,:,jk,Kaa) = vv(:,:,jk,Kaa) + zvb(:,:)*vmask(:,:,jk) 
    387369      END DO 
    388  
    389 !!st      DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
    390 !!st         uu(ji,jj,jk,Kaa) = uu(ji,jj,jk,Kaa) + zub(ji,jj)*umask(ji,jj,jk) 
    391 !!st         vv(ji,jj,jk,Kaa) = vv(ji,jj,jk,Kaa) + zvb(ji,jj)*vmask(ji,jj,jk) 
    392 !!st      END_3D 
    393370          
    394371 
     
    401378            CALL Agrif_dyn( kstp, kstg ) 
    402379# endif 
    403       !                                        ! local domain boundaries  (T-point, unchanged sign) 
     380      !                                              !* local domain boundaries  (T-point, unchanged sign) 
    404381      CALL lbc_lnk_multi( 'stp_RK3_stg', uu(:,:,:,       Kaa), 'U', -1., vv(:,:,:       ,Kaa), 'V', -1.   & 
    405382         &                             , ts(:,:,:,jp_tem,Kaa), 'T',  1., ts(:,:,:,jp_sal,Kaa), 'T',  1. ) 
    406383      ! 
    407       !                                        !* BDY open boundaries 
     384      !                                              !* BDY open boundaries 
    408385      IF( ln_bdy )   THEN 
    409386                               CALL bdy_tra( kstp, Kbb, ts,     Kaa ) 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/TRP/trctrp.F90

    r15189 r15321  
    66   !! History :   1.0  !  2004-03 (C. Ethe) Original code 
    77   !!             3.3  !  2010-07 (C. Ethe) Merge TRA-TRC 
     8   !!             4.x  !  2021-08 (S. Techene, G. Madec) Adapt for RK3 time-stepping 
    89   !!---------------------------------------------------------------------- 
    910#if defined key_top 
     
    3839   PRIVATE 
    3940 
    40    PUBLIC   trc_trp    ! called by trc_stp 
     41   PUBLIC   trc_trp    ! called by trc_stp and stprk3_stg 
    4142 
    4243   !!---------------------------------------------------------------------- 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/trcrst.F90

    r15191 r15321  
    88   !!              -   !  2005-10 (C. Ethe) print control 
    99   !!             2.0  !  2005-10 (C. Ethe, G. Madec) revised architecture 
     10   !!             4.x  !  2021-08 (S. Techene, G. Madec) RK3  time-stepping only deals with before read/write 
    1011   !!---------------------------------------------------------------------- 
    1112#if defined key_top 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/trcstp_rk3.F90

    r15281 r15321  
    66   !! History :  1.0  !  2004-03  (C. Ethe)  Original 
    77   !!            4.1  !  2019-08  (A. Coward, D. Storkey) rewrite in preparation for new timestepping scheme 
     8   !!            4.x  !  2021-08  (S. Techene, G. Madec) preparation and finalisation for RK3 time-stepping only 
    89   !!---------------------------------------------------------------------- 
    910#if defined key_top 
    1011   !!---------------------------------------------------------------------- 
    11    !!   trc_stp       : passive tracer system time-stepping 
     12   !!   trc_stp_start : prepare  passive tracer system time-stepping 
     13   !!   trc_stp_end   : finalise passive tracer system time-stepping 
    1214   !!---------------------------------------------------------------------- 
    1315   USE par_trc        ! need jptra, number of passive tracers 
     
    5254      !!                     ***  ROUTINE trc_stp_start  *** 
    5355      !!                       
    54       !! ** Purpose :   Time loop of opa for passive tracer 
     56      !! ** Purpose :   Prepare time loop of opa for passive tracer 
    5557      !!  
    5658      !! ** Method  :   Compute the passive tracers trends  
    5759      !!                Update the passive tracers 
     60      !!                Manage restart file 
    5861      !!------------------------------------------------------------------- 
    5962      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index 
     
    6871      l_trcstat  = ( sn_cfctl%l_trcstat ) .AND. & 
    6972           &       ( ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) ) 
    70 !!st should be in init of top 
     73      ! 
    7174      IF( kt == nittrc000 )                      CALL trc_stp_ctl   ! control  
    7275      IF( kt == nittrc000 .AND. lk_trdmxl_trc )  CALL trd_mxl_trc_init    ! trends: Mixed-layer 
    73 !!st-gm 
    74 !!st-gm a faire uniquement au stage 3 
    75 !!st      ! 
     76      ! 
    7677      IF( .NOT.ln_linssh ) THEN                                           ! update ocean volume due to ssh temporal evolution 
    7778         DO jk = 1, jpk 
     
    8485      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt ) 
    8586      !     
    86       ! 
    8787      IF(sn_cfctl%l_prttrc) THEN 
    8888         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
     
    9090      ENDIF 
    9191      ! 
    92 !!st      tr(:,:,:,:,Krhs) = 0._wp 
    93       ! 
    9492      CALL trc_rst_opn  ( kt )                            ! Open tracer restart file  
    9593      IF( lrst_trc )  CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar 
    96 !!st cf. stage 3      CALL trc_wri      ( kt,      Kmm            )       ! output of passive tracers with iom I/O manager 
    9794      ! 
    9895      IF( ln_timing )   CALL timing_stop('trc_stp_start') 
     
    10198 
    10299 
    103    SUBROUTINE trc_stp( kt, Kbb, Kmm, Krhs, Kaa ) 
    104       !!------------------------------------------------------------------- 
    105       !!                     ***  ROUTINE trc_stp  *** 
     100   SUBROUTINE trc_stp_end( kt, Kbb, Kmm, Kaa ) 
     101      !!------------------------------------------------------------------- 
     102      !!                     ***  ROUTINE trc_stp_end  *** 
    106103      !!                       
    107       !! ** Purpose :   Time loop of opa for passive tracer 
     104      !! ** Purpose :   Finalise time loop of opa for passive tracer 
    108105      !!  
    109       !! ** Method  :   Compute the passive tracers trends  
    110       !!                Update the passive tracers 
     106      !! ** Method  :   Write restart and outputs  
    111107      !!------------------------------------------------------------------- 
    112108      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index 
    113       INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices 
     109      INTEGER, INTENT( in ) :: Kbb, Kmm, Kaa ! time level indices 
    114110      ! 
    115111      INTEGER ::   jk, jn   ! dummy loop indices 
     
    118114      !!------------------------------------------------------------------- 
    119115      ! 
    120       IF( ln_timing )   CALL timing_start('trc_stp') 
    121       ! 
    122       IF( l_1st_euler .OR. ln_top_euler ) THEN     ! at nittrc000 
    123          rDt_trc =  rn_Dt           ! = rn_Dt (use or restarting with Euler time stepping) 
    124       ELSEIF( kt <= nittrc000 + 1 ) THEN                                     ! at nittrc000 or nittrc000+1  
    125          rDt_trc = 2. * rn_Dt       ! = 2 rn_Dt (leapfrog)  
    126       ENDIF 
    127       ! 
    128       IF( .NOT.ln_linssh ) THEN                                           ! update ocean volume due to ssh temporal evolution 
    129          DO jk = 1, jpk 
    130             cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
    131          END DO 
    132          IF ( l_trcstat .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend )   & 
    133             & .OR. iom_use( "pno3tot" ) .OR. iom_use( "ppo4tot" ) .OR. iom_use( "psiltot" )   & 
    134             & .OR. iom_use( "palktot" ) .OR. iom_use( "pfertot" ) )                           & 
    135             &     areatot = glob_sum( 'trcstp', cvol(:,:,:) ) 
    136       ENDIF 
    137       ! 
    138       tr(:,:,:,:,Krhs) = 0._wp 
    139       ! 
    140       CALL trc_wri      ( kt,      Kmm            )       ! output of passive tracers with iom I/O manager 
    141       CALL trc_sms      ( kt, Kbb, Kmm, Krhs      )       ! tracers: sinks and sources 
    142       CALL trc_trp      ( kt, Kbb, Kmm, Krhs, Kaa )       ! transport of passive tracers 
    143            ! 
     116      IF( ln_timing )   CALL timing_start('trc_stp_end') 
     117      ! 
     118      ! 
    144119           ! Note passive tracers have been time-filtered in trc_trp but the time level 
    145120           ! indices will not be swapped until after tra_atf/dyn_atf/ssh_atf in stp. Subsequent calls here 
     
    152127         IF(lwm) CALL FLUSH( numont )                     ! flush namelist output 
    153128      ENDIF 
    154       IF( lrst_trc )            CALL trc_rst_wri  ( kt, Kbb, Kmm, Kaa  )       ! write tracer restart file 
    155       IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,      Kaa       )       ! trends: Mixed-layer 
    156       ! 
    157       IF( ln_top_euler ) THEN  
    158          ! For Euler timestepping for TOP we need to copy the "after" to the "now" fields  
    159          ! here then after the (leapfrog) swapping of the time-level indices in OCE/step.F90 we have  
    160          ! "before" fields = "now" fields. 
    161          tr(:,:,:,:,Kmm) = tr(:,:,:,:,Kaa) 
    162       ENDIF 
    163       ! 
    164       IF (l_trcstat) THEN 
    165          ztrai = 0._wp                                                   !  content of all tracers 
    166          DO jn = 1, jptra 
    167             ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Kaa) * cvol(:,:,:)   ) 
    168          END DO 
    169          IF( lwm ) WRITE(numstr,9300) kt,  ztrai / areatot 
    170       ENDIF 
    171 9300  FORMAT(i10,D23.16) 
    172       ! 
    173       IF( ln_timing )   CALL timing_stop('trc_stp') 
    174       ! 
    175    END SUBROUTINE trc_stp 
    176  
    177  
    178    SUBROUTINE trc_stp_end( kt, Kbb, Kmm, Kaa ) 
    179       !!------------------------------------------------------------------- 
    180       !!                     ***  ROUTINE trc_stp_end  *** 
    181       !!                       
    182       !! ** Purpose :   Time loop of opa for passive tracer 
    183       !!  
    184       !! ** Method  :   Compute the passive tracers trends  
    185       !!                Update the passive tracers 
    186       !!------------------------------------------------------------------- 
    187       INTEGER, INTENT( in ) :: kt                  ! ocean time-step index 
    188       INTEGER, INTENT( in ) :: Kbb, Kmm, Kaa ! time level indices 
    189       ! 
    190       INTEGER ::   jk, jn   ! dummy loop indices 
    191       REAL(wp)::   ztrai    ! local scalar 
    192       CHARACTER (len=25) ::   charout   ! 
    193       !!------------------------------------------------------------------- 
    194       ! 
    195       IF( ln_timing )   CALL timing_start('trc_stp_end') 
    196       ! 
    197             ! 
    198            ! Note passive tracers have been time-filtered in trc_trp but the time level 
    199            ! indices will not be swapped until after tra_atf/dyn_atf/ssh_atf in stp. Subsequent calls here 
    200            ! anticipate this update which will be: Nrhs= Nbb ; Nbb = Nnn ; Nnn = Naa ; Naa = Nrhs 
    201            ! and use the filtered levels explicitly. 
    202            ! 
    203       IF( kt == nittrc000 ) THEN 
    204          CALL iom_close( numrtr )                         ! close input tracer restart file 
    205          IF(lrxios) CALL iom_context_finalize(      cr_toprst_cxt          ) 
    206          IF(lwm) CALL FLUSH( numont )                     ! flush namelist output 
    207       ENDIF 
    208129      IF( lrst_trc )            CALL trc_rst_wri  ( kt, Kbb, Kmm, Kaa )       ! write tracer restart file 
    209130      IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,           Kaa )       ! trends: Mixed-layer 
    210131      ! 
    211132      IF (l_trcstat) THEN 
    212          ztrai = 0._wp                                                   !  content of all tracers 
     133         ztrai = 0._wp                                    !  content of all tracers 
    213134         DO jn = 1, jptra 
    214135            ztrai = ztrai + glob_sum( 'trcstp_rk3', tr(:,:,:,jn,Kaa) * cvol(:,:,:)   ) !!st cvol@Kmm weird !! 
     
    2191409300  FORMAT(i10,D23.16) 
    220141      ! 
    221       CALL trc_wri      ( kt,      Kaa            )       ! output of passive tracers with iom I/O manager (!!st Kbb car après le swap des indices !!st-correction FAUX on est avant : le swap a lieu après le CALL à stp_RK3_stg(3) ) 
     142      CALL trc_wri      ( kt,      Kaa            )       ! output of passive tracers with iom I/O manager before time level swap  
    222143      ! 
    223144      IF( ln_timing )   CALL timing_stop('trc_stp_end') 
Note: See TracChangeset for help on using the changeset viewer.