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 12581 for NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/TRA/traatf.F90 – NEMO

Ignore:
Timestamp:
2020-03-20T23:26:56+01:00 (4 years ago)
Author:
techene
Message:

OCE/DOM/domqe.F90: make dom_qe_r3c public, OCE/DYN/dynatfLF.F90: duplicate dynatf and replace dom_qe_interpol calls by the ssh scaling method to compute and update e3t/u/v at time Kmm, OCE/TRA/traatfLF.F90: duplicate traatf and replace dom_qe_interpol by the ssh scaling method to compute internal ze3t, OCE/steplf.F90: change the order of atf routines ssh_atf is called first then dom_qe_r3c to computed filtered ssh to h ratios at T-, U-, V-points finally tra_atf_lf and dyn_atf_lf

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/TRA/traatf.F90

    r12377 r12581  
    2626   !!---------------------------------------------------------------------- 
    2727   USE oce             ! ocean dynamics and tracers variables 
    28    USE dom_oce         ! ocean space and time domain variables  
     28   USE dom_oce         ! ocean space and time domain variables 
    2929   USE sbc_oce         ! surface boundary condition: ocean 
    3030   USE sbcrnf          ! river runoffs 
     
    3333   USE domvvl          ! variable volume 
    3434   USE trd_oce         ! trends: ocean variables 
    35    USE trdtra          ! trends manager: tracers  
     35   USE trdtra          ! trends manager: tracers 
    3636   USE traqsr          ! penetrative solar radiation (needed for nksr) 
    3737   USE phycst          ! physical constant 
     
    6969      !!                   ***  ROUTINE traatf  *** 
    7070      !! 
    71       !! ** Purpose :   Apply the boundary condition on the after temperature   
     71      !! ** Purpose :   Apply the boundary condition on the after temperature 
    7272      !!             and salinity fields and add the Asselin time filter on now fields. 
    73       !!  
    74       !! ** Method  :   At this stage of the computation, ta and sa are the  
     73      !! 
     74      !! ** Method  :   At this stage of the computation, ta and sa are the 
    7575      !!             after temperature and salinity as the time stepping has 
    7676      !!             been performed in trazdf_imp or trazdf_exp module. 
    7777      !! 
    78       !!              - Apply lateral boundary conditions on (ta,sa)  
    79       !!             at the local domain   boundaries through lbc_lnk call,  
    80       !!             at the one-way open boundaries (ln_bdy=T),  
     78      !!              - Apply lateral boundary conditions on (ta,sa) 
     79      !!             at the local domain   boundaries through lbc_lnk call, 
     80      !!             at the one-way open boundaries (ln_bdy=T), 
    8181      !!             at the AGRIF zoom   boundaries (lk_agrif=T) 
    8282      !! 
     
    8888      INTEGER                                  , INTENT(in   ) :: kt             ! ocean time-step index 
    8989      INTEGER                                  , INTENT(in   ) :: Kbb, Kmm, Kaa  ! time level indices 
    90       REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts            ! active tracers  
     90      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts            ! active tracers 
    9191      !! 
    9292      INTEGER  ::   ji, jj, jk, jn   ! dummy loop indices 
     
    104104 
    105105      ! Update after tracer on domain lateral boundaries 
    106       !  
     106      ! 
    107107#if defined key_agrif 
    108108      CALL Agrif_tra                     ! AGRIF zoom boundaries 
     
    112112      ! 
    113113      IF( ln_bdy )   CALL bdy_tra( kt, Kbb, pts, Kaa )  ! BDY open boundaries 
    114   
     114 
    115115      ! set time step size (Euler/Leapfrog) 
    116116      IF( neuler == 0 .AND. kt == nit000 ) THEN   ;   r2dt =        rdt   ! at nit000             (Euler) 
     
    119119 
    120120      ! trends computation initialisation 
    121       IF( l_trdtra )   THEN                     
     121      IF( l_trdtra )   THEN 
    122122         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 
    123123         ztrdt(:,:,jpk) = 0._wp 
    124124         ztrds(:,:,jpk) = 0._wp 
    125          IF( ln_traldf_iso ) THEN              ! diagnose the "pure" Kz diffusive trend  
     125         IF( ln_traldf_iso ) THEN              ! diagnose the "pure" Kz diffusive trend 
    126126            CALL trd_tra( kt, Kmm, Kaa, 'TRA', jp_tem, jptra_zdfp, ztrdt ) 
    127127            CALL trd_tra( kt, Kmm, Kaa, 'TRA', jp_sal, jptra_zdfp, ztrds ) 
    128128         ENDIF 
    129          ! total trend for the non-time-filtered variables.  
     129         ! total trend for the non-time-filtered variables. 
    130130         zfact = 1.0 / rdt 
    131131         ! G Nurser 23 Mar 2017. Recalculate trend as Delta(e3t*T)/e3tn; e3tn cancel from pts(Kmm) terms 
     
    137137         CALL trd_tra( kt, Kmm, Kaa, 'TRA', jp_sal, jptra_tot, ztrds ) 
    138138         IF( ln_linssh ) THEN       ! linear sea surface height only 
    139             ! Store now fields before applying the Asselin filter  
     139            ! Store now fields before applying the Asselin filter 
    140140            ! in order to calculate Asselin filter trend later. 
    141             ztrdt(:,:,:) = pts(:,:,:,jp_tem,Kmm)  
     141            ztrdt(:,:,:) = pts(:,:,:,jp_tem,Kmm) 
    142142            ztrds(:,:,:) = pts(:,:,:,jp_sal,Kmm) 
    143143         ENDIF 
    144144      ENDIF 
    145145 
    146       IF( neuler == 0 .AND. kt == nit000 ) THEN       ! Euler time-stepping  
     146      IF( neuler == 0 .AND. kt == nit000 ) THEN       ! Euler time-stepping 
    147147         ! 
    148148         IF (l_trdtra .AND. .NOT. ln_linssh ) THEN   ! Zero Asselin filter contribution must be explicitly written out since for vvl 
     
    156156      ELSE                                            ! Leap-Frog + Asselin filter time stepping 
    157157         ! 
    158          IF( ln_linssh ) THEN   ;   CALL tra_atf_fix( kt, Kbb, Kmm, Kaa, nit000,      'TRA', pts, jpts )  ! linear free surface  
     158         IF( ln_linssh ) THEN   ;   CALL tra_atf_fix( kt, Kbb, Kmm, Kaa, nit000,      'TRA', pts, jpts )  ! linear free surface 
    159159         ELSE                   ;   CALL tra_atf_vvl( kt, Kbb, Kmm, Kaa, nit000, rdt, 'TRA', pts, sbc_tsc, sbc_tsc_b, jpts )  ! non-linear free surface 
    160160         ENDIF 
     
    164164                  &                    pts(:,:,:,jp_tem,Kaa), 'T', 1., pts(:,:,:,jp_sal,Kaa), 'T', 1.  ) 
    165165         ! 
    166       ENDIF      
    167       ! 
    168       IF( l_trdtra .AND. ln_linssh ) THEN      ! trend of the Asselin filter (tb filtered - tb)/dt      
    169          zfact = 1._wp / r2dt              
     166      ENDIF 
     167      ! 
     168      IF( l_trdtra .AND. ln_linssh ) THEN      ! trend of the Asselin filter (tb filtered - tb)/dt 
     169         zfact = 1._wp / r2dt 
    170170         DO jk = 1, jpkm1 
    171171            ztrdt(:,:,jk) = ( pts(:,:,jk,jp_tem,Kmm) - ztrdt(:,:,jk) ) * zfact 
     
    191191      !! 
    192192      !! ** Purpose :   fixed volume: apply the Asselin time filter to the "now" field 
    193       !!  
     193      !! 
    194194      !! ** Method  : - Apply a Asselin time filter on now fields. 
    195195      !! 
     
    216216         ! 
    217217         DO_3D_00_00( 1, jpkm1 ) 
    218             ztn = pt(ji,jj,jk,jn,Kmm)                                     
     218            ztn = pt(ji,jj,jk,jn,Kmm) 
    219219            ztd = pt(ji,jj,jk,jn,Kaa) - 2._wp * ztn + pt(ji,jj,jk,jn,Kbb)  ! time laplacian on tracers 
    220220            ! 
     
    231231      !!                   ***  ROUTINE tra_atf_vvl  *** 
    232232      !! 
    233       !! ** Purpose :   Time varying volume: apply the Asselin time filter   
    234       !!  
     233      !! ** Purpose :   Time varying volume: apply the Asselin time filter 
     234      !! 
    235235      !! ** Method  : - Apply a thickness weighted Asselin time filter on now fields. 
    236236      !!             pt(Kmm)  = ( e3t(Kmm)*pt(Kmm) + atfp*[ e3t(Kbb)*pt(Kbb) - 2 e3t(Kmm)*pt(Kmm) + e3t_a*pt(Kaa) ] ) 
     
    262262      ENDIF 
    263263      ! 
    264       IF( cdtype == 'TRA' )  THEN    
     264      IF( cdtype == 'TRA' )  THEN 
    265265         ll_traqsr  = ln_traqsr        ! active  tracers case  and  solar penetration 
    266266         ll_rnf     = ln_rnf           ! active  tracers case  and  river runoffs 
     
    268268      ELSE                          ! passive tracers case 
    269269         ll_traqsr  = .FALSE.          ! NO solar penetration 
    270          ll_rnf     = .FALSE.          ! NO river runoffs ????          !!gm BUG ?   
    271          ll_isf     = .FALSE.          ! NO ice shelf melting/freezing  !!gm BUG ??  
     270         ll_rnf     = .FALSE.          ! NO river runoffs ????          !!gm BUG ? 
     271         ll_isf     = .FALSE.          ! NO ice shelf melting/freezing  !!gm BUG ?? 
    272272      ENDIF 
    273273      ! 
     
    279279      zfact1 = atfp * p2dt 
    280280      zfact2 = zfact1 * r1_rau0 
    281       DO jn = 1, kjpt       
     281      DO jn = 1, kjpt 
    282282         DO_3D_00_00( 1, jpkm1 ) 
    283283            ze3t_b = e3t(ji,jj,jk,Kbb) 
     
    296296            ! 
    297297            ! Add asselin correction on scale factors: 
    298             zscale = tmask(ji,jj,jk) * e3t(ji,jj,jk,Kmm) / ( ht(ji,jj) + 1._wp - ssmask(ji,jj) )  
    299             ze3t_f = ze3t_f - zfact2 * zscale * ( emp_b(ji,jj) - emp(ji,jj) )  
    300             IF ( ll_rnf ) ze3t_f = ze3t_f + zfact2 * zscale * (    rnf_b(ji,jj) -    rnf(ji,jj) )  
     298            zscale = tmask(ji,jj,jk) * e3t(ji,jj,jk,Kmm) / ( ht(ji,jj) + 1._wp - ssmask(ji,jj) ) 
     299            ze3t_f = ze3t_f - zfact2 * zscale * ( emp_b(ji,jj) - emp(ji,jj) ) 
     300            IF ( ll_rnf ) ze3t_f = ze3t_f + zfact2 * zscale * (    rnf_b(ji,jj) -    rnf(ji,jj) ) 
    301301            IF ( ll_isf ) THEN 
    302302               IF ( ln_isfcav_mlt ) ze3t_f = ze3t_f - zfact2 * zscale * ( fwfisf_cav_b(ji,jj) - fwfisf_cav(ji,jj) ) 
     
    304304            ENDIF 
    305305            ! 
    306             IF( jk == mikt(ji,jj) ) THEN           ! first level  
     306            IF( jk == mikt(ji,jj) ) THEN           ! first level 
    307307               ztc_f  = ztc_f  - zfact1 * ( psbc_tc(ji,jj,jn) - psbc_tc_b(ji,jj,jn) ) 
    308308            ENDIF 
    309309            ! 
    310310            ! solar penetration (temperature only) 
    311             IF( ll_traqsr .AND. jn == jp_tem .AND. jk <= nksr )                            &  
    312                &     ztc_f  = ztc_f  - zfact1 * ( qsr_hc(ji,jj,jk) - qsr_hc_b(ji,jj,jk) )  
     311            IF( ll_traqsr .AND. jn == jp_tem .AND. jk <= nksr )                            & 
     312               &     ztc_f  = ztc_f  - zfact1 * ( qsr_hc(ji,jj,jk) - qsr_hc_b(ji,jj,jk) ) 
    313313               ! 
    314314            ! 
    315315            IF( ll_rnf .AND. jk <= nk_rnf(ji,jj) )                                          & 
    316                &     ztc_f  = ztc_f  - zfact1 * ( rnf_tsc(ji,jj,jn) - rnf_tsc_b(ji,jj,jn) ) &  
     316               &     ztc_f  = ztc_f  - zfact1 * ( rnf_tsc(ji,jj,jn) - rnf_tsc_b(ji,jj,jn) ) & 
    317317               &                              * e3t(ji,jj,jk,Kmm) / h_rnf(ji,jj) 
    318318 
     
    328328                        &                     * e3t(ji,jj,jk,Kmm) / rhisf_tbl_cav(ji,jj) 
    329329                  END IF 
    330                   ! level partially include in Losch_2008 ice shelf boundary layer  
     330                  ! level partially include in Losch_2008 ice shelf boundary layer 
    331331                  IF ( jk == misfkb_cav(ji,jj) ) THEN 
    332332                     ztc_f  = ztc_f  - zfact1 * ( risf_cav_tsc(ji,jj,jn) - risf_cav_tsc_b(ji,jj,jn) )  & 
     
    342342                            &                 * e3t(ji,jj,jk,Kmm) / rhisf_tbl_par(ji,jj) 
    343343                  END IF 
    344                   ! level partially include in Losch_2008 ice shelf boundary layer  
     344                  ! level partially include in Losch_2008 ice shelf boundary layer 
    345345                  IF ( jk == misfkb_par(ji,jj) ) THEN 
    346346                     ztc_f  = ztc_f  - zfact1 * ( risf_par_tsc(ji,jj,jn) - risf_par_tsc_b(ji,jj,jn) )  & 
     
    371371            ! 
    372372         END_3D 
    373          !  
     373         ! 
    374374      END DO 
    375375      ! 
    376376      IF( ( l_trdtra .AND. cdtype == 'TRA' ) .OR. ( l_trdtrc .AND. cdtype == 'TRC' ) )   THEN 
    377          IF( l_trdtra .AND. cdtype == 'TRA' ) THEN  
     377         IF( l_trdtra .AND. cdtype == 'TRA' ) THEN 
    378378            CALL trd_tra( kt, Kmm, Kaa, cdtype, jp_tem, jptra_atf, ztrd_atf(:,:,:,jp_tem) ) 
    379379            CALL trd_tra( kt, Kmm, Kaa, cdtype, jp_sal, jptra_atf, ztrd_atf(:,:,:,jp_sal) ) 
Note: See TracChangeset for help on using the changeset viewer.