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 12928 for NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/OCE/DYN/dynspg_exp.F90 – NEMO

Ignore:
Timestamp:
2020-05-14T21:46:00+02:00 (4 years ago)
Author:
smueller
Message:

Synchronizing with /NEMO/trunk@12925 (ticket #2170)

Location:
NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser

    • Property svn:externals
      •  

        old new  
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@HEAD         sette 
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/OCE/DYN/dynspg_exp.F90

    r10068 r12928  
    3030 
    3131   !! * Substitutions 
    32 #  include "vectopt_loop_substitute.h90" 
     32#  include "do_loop_substitute.h90" 
    3333   !!---------------------------------------------------------------------- 
    3434   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    3838CONTAINS 
    3939 
    40    SUBROUTINE dyn_spg_exp( kt ) 
     40   SUBROUTINE dyn_spg_exp( kt, Kmm, puu, pvv, Krhs ) 
    4141      !!---------------------------------------------------------------------- 
    4242      !!                  ***  routine dyn_spg_exp  *** 
     
    4848      !! ** Method  :   Explicit free surface formulation. Add to the general 
    4949      !!              momentum trend the surface pressure gradient : 
    50       !!                      (ua,va) = (ua,va) + (spgu,spgv) 
    51       !!              where spgu = -1/rau0 d/dx(ps) = -g/e1u di( sshn ) 
    52       !!                    spgv = -1/rau0 d/dy(ps) = -g/e2v dj( sshn ) 
     50      !!                      (uu(rhs),vv(rhs)) = (uu(rhs),vv(rhs)) + (spgu,spgv) 
     51      !!              where spgu = -1/rho0 d/dx(ps) = -g/e1u di( ssh(now) ) 
     52      !!                    spgv = -1/rho0 d/dy(ps) = -g/e2v dj( ssh(now) ) 
    5353      !! 
    54       !! ** Action :   (ua,va)   trend of horizontal velocity increased by  
     54      !! ** Action :   (puu(:,:,:,Krhs),pvv(:,:,:,Krhs))   trend of horizontal velocity increased by  
    5555      !!                         the surf. pressure gradient trend 
    5656      !!--------------------------------------------------------------------- 
    57       INTEGER, INTENT(in)  ::   kt   ! ocean time-step index 
     57      INTEGER                             , INTENT( in )  ::  kt        ! ocean time-step index 
     58      INTEGER                             , INTENT( in )  ::  Kmm, Krhs ! ocean time level indices 
     59      REAL(wp), DIMENSION(jpi,jpj,jpk,jpt), INTENT(inout) ::  puu, pvv  ! ocean velocities and RHS of momentum equation 
    5860      !! 
    5961      INTEGER ::   ji, jj, jk   ! dummy loop indices 
     
    7274      IF( ln_linssh ) THEN          !* linear free surface : add the surface pressure gradient trend 
    7375         ! 
    74          DO jj = 2, jpjm1                    ! now surface pressure gradient 
    75             DO ji = fs_2, fs_jpim1   ! vector opt. 
    76                spgu(ji,jj) = - grav * ( sshn(ji+1,jj) - sshn(ji,jj) ) * r1_e1u(ji,jj) 
    77                spgv(ji,jj) = - grav * ( sshn(ji,jj+1) - sshn(ji,jj) ) * r1_e2v(ji,jj) 
    78             END DO  
    79          END DO 
     76         DO_2D_00_00 
     77            spgu(ji,jj) = - grav * ( ssh(ji+1,jj,Kmm) - ssh(ji,jj,Kmm) ) * r1_e1u(ji,jj) 
     78            spgv(ji,jj) = - grav * ( ssh(ji,jj+1,Kmm) - ssh(ji,jj,Kmm) ) * r1_e2v(ji,jj) 
     79         END_2D 
    8080         ! 
    81          DO jk = 1, jpkm1                    ! Add it to the general trend 
    82             DO jj = 2, jpjm1 
    83                DO ji = fs_2, fs_jpim1   ! vector opt. 
    84                   ua(ji,jj,jk) = ua(ji,jj,jk) + spgu(ji,jj) 
    85                   va(ji,jj,jk) = va(ji,jj,jk) + spgv(ji,jj) 
    86                END DO 
    87             END DO 
    88          END DO 
     81         DO_3D_00_00( 1, jpkm1 ) 
     82            puu(ji,jj,jk,Krhs) = puu(ji,jj,jk,Krhs) + spgu(ji,jj) 
     83            pvv(ji,jj,jk,Krhs) = pvv(ji,jj,jk,Krhs) + spgv(ji,jj) 
     84         END_3D 
    8985         ! 
    9086      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.