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 9250 for branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfdrg.F90 – NEMO

Ignore:
Timestamp:
2018-01-17T08:25:53+01:00 (6 years ago)
Author:
gm
Message:

dev_merge_2017 : HPC09_ZDF: drag finalization: move dyn_bfr routine in zdfdrg (renamed zdf_drg_exp) and delete dynbfr.F90 module - result unchanged

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfdrg.F90

    r9209 r9250  
    1616   !!---------------------------------------------------------------------- 
    1717   !!   zdf_drg       : update bottom friction coefficient (non-linear bottom friction only) 
     18   !!   zdf_drg_exp   : compute the top & bottom friction in explicit case 
    1819   !!   zdf_drg_init  : read in namdrg namelist and control the bottom friction parameters. 
    1920   !!       drg_init  : 
     
    2324   USE dom_oce        ! ocean space and time domain variables 
    2425   USE zdf_oce        ! ocean vertical physics variables 
     26   USE trd_oce        ! trends: ocean variables 
     27   USE trddyn         ! trend manager: dynamics 
    2528   ! 
    2629   USE in_out_manager ! I/O manager 
     
    3437 
    3538   PUBLIC   zdf_drg         ! called by zdf_phy 
     39   PUBLIC   zdf_drg_exp     ! called by dyn_zdf 
    3640   PUBLIC   zdf_drg_init    ! called by zdf_phy_init 
    3741 
     
    140144 
    141145 
     146   SUBROUTINE zdf_drg_exp( kt, pub, pvb, pua, pva ) 
     147      !!---------------------------------------------------------------------- 
     148      !!                  ***  ROUTINE zdf_drg_exp  *** 
     149      !! 
     150      !! ** Purpose :   compute and add the explicit top and bottom frictions. 
     151      !! 
     152      !! ** Method  :   in explicit case,  
     153      !! 
     154      !!              NB: in implicit case the calculation is performed in dynzdf.F90 
     155      !! 
     156      !! ** Action  :   (pua,pva)   momentum trend increased by top & bottom friction trend 
     157      !!--------------------------------------------------------------------- 
     158      INTEGER                         , INTENT(in   ) ::   kt         ! ocean time-step index 
     159      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pub, pvb   ! the two components of the before velocity 
     160      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pua, pva   ! the two components of the velocity tendency 
     161      !!  
     162      INTEGER  ::   ji, jj       ! dummy loop indexes 
     163      INTEGER  ::   ikbu, ikbv   ! local integers 
     164      REAL(wp) ::   zm1_2dt      ! local scalar 
     165      REAL(wp) ::   zCdu, zCdv   !   -      - 
     166      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrdu, ztrdv 
     167      !!--------------------------------------------------------------------- 
     168      ! 
     169!!gm bug : time step is only rdt (not 2 rdt if euler start !) 
     170      zm1_2dt = - 1._wp / ( 2._wp * rdt ) 
     171 
     172      IF( l_trddyn ) THEN      ! trends: store the input trends 
     173         ALLOCATE( ztrdu(jpi,jpj,jpk) , ztrdv(jpi,jpj,jpk) ) 
     174         ztrdu(:,:,:) = pua(:,:,:) 
     175         ztrdv(:,:,:) = pva(:,:,:) 
     176      ENDIF 
     177 
     178      DO jj = 2, jpjm1 
     179         DO ji = 2, jpim1 
     180            ikbu = mbku(ji,jj)          ! deepest wet ocean u- & v-levels 
     181            ikbv = mbkv(ji,jj) 
     182            ! 
     183            ! Apply stability criteria on absolute value  : abs(bfr/e3) < 1/(2dt) => bfr/e3 > -1/(2dt) 
     184            zCdu = 0.5*( rCdU_bot(ji+1,jj)+rCdU_bot(ji,jj) ) / e3u_n(ji,jj,ikbu) 
     185            zCdv = 0.5*( rCdU_bot(ji,jj+1)+rCdU_bot(ji,jj) ) / e3v_n(ji,jj,ikbv) 
     186            ! 
     187            pua(ji,jj,ikbu) = pua(ji,jj,ikbu) + MAX(  zCdu , zm1_2dt  ) * pub(ji,jj,ikbu) 
     188            pva(ji,jj,ikbv) = pva(ji,jj,ikbv) + MAX(  zCdv , zm1_2dt  ) * pvb(ji,jj,ikbv) 
     189         END DO 
     190      END DO 
     191      ! 
     192      IF( ln_isfcav ) THEN        ! ocean cavities 
     193         DO jj = 2, jpjm1 
     194            DO ji = 2, jpim1 
     195               ikbu = miku(ji,jj)          ! first wet ocean u- & v-levels 
     196               ikbv = mikv(ji,jj) 
     197               ! 
     198               ! Apply stability criteria on absolute value  : abs(bfr/e3) < 1/(2dt) => bfr/e3 > -1/(2dt) 
     199               zCdu = 0.5*( rCdU_top(ji+1,jj)+rCdU_top(ji,jj) ) / e3u_n(ji,jj,ikbu)    ! NB: Cdtop masked 
     200               zCdv = 0.5*( rCdU_top(ji,jj+1)+rCdU_top(ji,jj) ) / e3v_n(ji,jj,ikbv) 
     201               ! 
     202               pua(ji,jj,ikbu) = pua(ji,jj,ikbu) + MAX(  zCdu , zm1_2dt  ) * pub(ji,jj,ikbu) 
     203               pva(ji,jj,ikbv) = pva(ji,jj,ikbv) + MAX(  zCdv , zm1_2dt  ) * pvb(ji,jj,ikbv) 
     204           END DO 
     205         END DO 
     206      ENDIF 
     207      ! 
     208      IF( l_trddyn ) THEN      ! trends: send trends to trddyn for further diagnostics 
     209         ztrdu(:,:,:) = pua(:,:,:) - ztrdu(:,:,:) 
     210         ztrdv(:,:,:) = pva(:,:,:) - ztrdv(:,:,:) 
     211         CALL trd_dyn( ztrdu(:,:,:), ztrdv(:,:,:), jpdyn_bfr, kt ) 
     212         DEALLOCATE( ztrdu, ztrdv ) 
     213      ENDIF 
     214      !                                          ! print mean trends (used for debugging) 
     215      IF(ln_ctl)   CALL prt_ctl( tab3d_1=pua, clinfo1=' bfr  - Ua: ', mask1=umask,               & 
     216         &                       tab3d_2=pva, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     217      ! 
     218   END SUBROUTINE zdf_drg_exp 
     219 
     220 
    142221   SUBROUTINE zdf_drg_init 
    143222      !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.