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 14205 for NEMO/trunk/src/OCE/stpmlf.F90 – NEMO

Ignore:
Timestamp:
2020-12-17T19:23:48+01:00 (4 years ago)
Author:
techene
Message:

#2385 cosmetics and cleaning

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/stpmlf.F90

    r14201 r14205  
    5050   USE traatf_qco     ! time filtering                 (tra_atf_qco routine) 
    5151   USE dynatf_qco     ! time filtering                 (dyn_atf_qco routine) 
    52     
    53    USE bdydyn         ! ocean open boundary conditions (define bdy_dyn) 
    54  
    55 #if defined key_agrif 
    56    USE agrif_oce_interp 
    57 #endif 
    5852 
    5953   IMPLICIT NONE 
     
    6862#  include "do_loop_substitute.h90" 
    6963#  include "domzgr_substitute.h90" 
     64#  include "do_loop_substitute.h90" 
    7065   !!---------------------------------------------------------------------- 
    7166   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    9994      !!---------------------------------------------------------------------- 
    10095      INTEGER ::   ji, jj, jk, jtile   ! dummy loop indice 
    101       REAL(wp),              DIMENSION(jpi,jpj,jpk) ::   zgdept 
    102       REAL(wp), ALLOCATABLE, DIMENSION(:,:)         ::   zssh_f 
     96      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zgdept 
    10397      !! --------------------------------------------------------------------- 
    10498#if defined key_agrif 
     
    210204      !  Ocean dynamics : hdiv, ssh, e3, u, v, w 
    211205      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    212       DO jk = 1, jpk 
    213          zgdept(:,:,jk) = gdept(:,:,jk,Nnn) 
    214       END DO 
     206       
    215207                         CALL ssh_nxt    ( kstp, Nbb, Nnn, ssh,  Naa )   ! after ssh (includes call to div_hor) 
    216208      IF( .NOT.lk_linssh ) THEN 
     
    221213                         CALL wzv        ( kstp, Nbb, Nnn, Naa, ww  )    ! Nnn cross-level velocity 
    222214      IF( ln_zad_Aimp )  CALL wAimp      ( kstp,      Nnn           )    ! Adaptive-implicit vertical advection partitioning 
     215                         ALLOCATE( zgdept(jpi,jpj,jpk) ) 
     216                         DO jk = 1, jpk 
     217                            zgdept(:,:,jk) = gdept(:,:,jk,Nnn) 
     218                         END DO 
    223219                         CALL eos        ( ts(:,:,:,:,Nnn), rhd, rhop, zgdept ) ! now in situ density for hpg computation 
    224  
     220                         DEALLOCATE( zgdept ) 
    225221 
    226222                         uu(:,:,:,Nrhs) = 0._wp            ! set dynamics trends to zero 
     
    240236                         CALL dyn_hpg( kstp,      Nnn      , uu, vv, Nrhs )  ! horizontal gradient of Hydrostatic pressure 
    241237                         CALL dyn_spg( kstp, Nbb, Nnn, Nrhs, uu, vv, ssh, uu_b, vv_b, Naa )  ! surface pressure gradient 
    242  
    243                                                       ! With split-explicit free surface, since now transports have been updated and ssh(:,:,Nrhs) as well 
    244       IF( ln_dynspg_ts ) THEN                         ! vertical scale factors and vertical velocity need to be updated 
     238                          
     239      IF( ln_dynspg_ts ) THEN      ! With split-explicit free surface, since now transports have been updated and ssh(:,:,Nrhs) 
     240                                   ! as well as vertical scale factors and vertical velocity need to be updated 
    245241                            CALL div_hor    ( kstp, Nbb, Nnn )                ! Horizontal divergence  (2nd call in time-split case) 
    246          IF(.NOT.lk_linssh) CALL dom_qco_r3c ( ssh(:,:,Naa), r3t(:,:,Naa), r3u(:,:,Naa), r3v(:,:,Naa), r3f(:,:) )   ! update ssh/h_0 ratio at t,u,v,f pts  
     242         IF(.NOT.lk_linssh) CALL dom_qco_r3c( ssh(:,:,Naa), r3t(:,:,Naa), r3u(:,:,Naa), r3v(:,:,Naa), r3f(:,:) )   ! update ssh/h_0 ratio at t,u,v,f pts  
    247243      ENDIF 
    248244                            CALL dyn_zdf    ( kstp, Nbb, Nnn, Nrhs, uu, vv, Naa  )  ! vertical diffusion 
     
    307303 
    308304#if defined key_agrif 
    309       IF(.NOT. Agrif_Root()) THEN 
     305      IF(.NOT. Agrif_Root() ) THEN 
    310306         IF( ln_tile    )   CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 ) 
    311307                            CALL Agrif_Sponge_tra        ! tracers sponge 
     
    319315                            CALL tra_adv    ( kstp, Nbb, Nnn, ts, Nrhs )  ! hor. + vert. advection ==> RHS 
    320316         IF( ln_zdfmfc  )   CALL tra_mfc    ( kstp, Nbb,      ts, Nrhs )  ! Mass Flux Convection 
    321          IF( ln_zdfosm  )   CALL tra_osm    ( kstp,      Nnn, ts, Nrhs )  ! OSMOSIS non-local tracer fluxes ==> RHS 
    322          IF( lrst_oce .AND. ln_zdfosm )   & 
    323             &               CALL osm_rst    ( kstp,      Nnn, 'WRITE'  )  ! write OSMOSIS outputs + ww (so must do here) to restarts 
     317         IF( ln_zdfosm  ) THEN 
     318                            CALL tra_osm    ( kstp,      Nnn, ts, Nrhs )  ! OSMOSIS non-local tracer fluxes ==> RHS 
     319            IF( lrst_oce )  CALL osm_rst    ( kstp,      Nnn, 'WRITE'  )  ! write OSMOSIS outputs + ww (so must do here) to restarts 
     320         ENDIF 
    324321                            CALL tra_ldf    ( kstp, Nbb, Nnn, ts, Nrhs )  ! lateral mixing 
    325322 
     
    391388      IF( Agrif_NbStepint() == 0 .AND. nstop == 0 )   & 
    392389         &               CALL Agrif_update_all( )                  ! Update all components 
    393       ENDIF 
    394390 
    395391#endif 
     
    494490      !! ** Action :   puu(Kaa),pvv(Kaa)   after horizontal velocity and tracers 
    495491      !!---------------------------------------------------------------------- 
     492#if defined key_agrif 
     493      USE agrif_oce_interp 
     494#endif 
     495      USE bdydyn         ! ocean open boundary conditions (define bdy_dyn) 
     496      !! 
    496497      INTEGER                                  , INTENT(in   ) ::   kt         ! ocean time-step index 
    497498      INTEGER                                  , INTENT(in   ) ::   Kbb, Kaa   ! before and after time level indices 
Note: See TracChangeset for help on using the changeset viewer.