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

Changeset 14863


Ignore:
Timestamp:
2021-05-14T11:31:05+02:00 (3 years ago)
Author:
smueller
Message:

Synchronizing with /NEMO/trunk@14857 (ticket #2353)

Location:
NEMO/branches/2021/dev_r14122_HPC-08_Mueller_OSMOSIS_streamlining
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14122_HPC-08_Mueller_OSMOSIS_streamlining/src/OCE/TRA/traadv_fct.F90

    r14856 r14863  
    164164         END_3D 
    165165         !                               !* upstream tracer flux in the k direction *! 
    166          DO_3D( 1, 1, 1, 1, 2, jpkm1 )      ! Interior value ( multiplied by wmask) 
     166         DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )      ! Interior value ( multiplied by wmask) 
    167167            zfp_wk = pW(ji,jj,jk) + ABS( pW(ji,jj,jk) ) 
    168168            zfm_wk = pW(ji,jj,jk) - ABS( pW(ji,jj,jk) ) 
     
    171171         IF( ln_linssh ) THEN               ! top ocean value (only in linear free surface as zwz has been w-masked) 
    172172            IF( ln_isfcav ) THEN                        ! top of the ice-shelf cavities and at the ocean surface 
    173                DO_2D( 1, 1, 1, 1 ) 
     173               DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    174174                  zwz(ji,jj, mikt(ji,jj) ) = pW(ji,jj,mikt(ji,jj)) * pt(ji,jj,mikt(ji,jj),jn,Kbb)   ! linear free surface 
    175175               END_2D 
    176176            ELSE                                        ! no cavities: only at the ocean surface 
    177                DO_2D( 1, 1, 1, 1 ) 
     177               DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    178178                  zwz(ji,jj,1) = pW(ji,jj,1) * pt(ji,jj,1,jn,Kbb) 
    179179               END_2D 
  • NEMO/branches/2021/dev_r14122_HPC-08_Mueller_OSMOSIS_streamlining/tests/ISOMIP+/MY_SRC/dtatsd.F90

    r14090 r14863  
    168168      INTEGER ::   ji, jj, jk, jl, jkk   ! dummy loop indicies 
    169169      INTEGER ::   ik, il0, il1, ii0, ii1, ij0, ij1   ! local integers 
    170       INTEGER ::   itile 
    171170      REAL(wp)::   zl, zi                             ! local scalars 
    172171      REAL(wp), DIMENSION(jpk) ::  ztp, zsp   ! 1D workspace 
    173172      !!---------------------------------------------------------------------- 
    174173      ! 
    175       IF( ntile == 0 .OR. ntile == 1 )  THEN                                         ! Do only for the full domain 
    176          itile = ntile 
    177          IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = 0 )            ! Use full domain 
     174      IF( .NOT. l_istiled .OR. ntile == 1 )  THEN                                         ! Do only for the full domain 
     175         IF( ln_tile ) CALL dom_tile_stop( ldhold=.TRUE. )             ! Use full domain 
    178176 
    179177         SELECT CASE(cddta) 
     
    186184         END SELECT 
    187185 
    188          IF( ln_tile ) CALL dom_tile( ntsi, ntsj, ntei, ntej, ktile = itile )            ! Revert to tile domain 
     186         IF( ln_tile ) CALL dom_tile_start( ldhold=.TRUE. )            ! Revert to tile domain 
    189187      ENDIF 
    190188      ! 
     
    206204      IF( ln_sco ) THEN                   !==   s- or mixed s-zps-coordinate   ==! 
    207205         ! 
    208          IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
     206         IF( .NOT. l_istiled .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    209207            IF( kt == nit000 .AND. lwp )THEN 
    210208               WRITE(numout,*) 
     
    213211         ENDIF 
    214212         ! 
    215          DO_2D( 1, 1, 1, 1 )                  ! vertical interpolation of T & S 
     213         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )                  ! vertical interpolation of T & S 
    216214            DO jk = 1, jpk                        ! determines the intepolated T-S profiles at each (i,j) points 
    217215               zl = gdept_0(ji,jj,jk) 
     
    248246         ! 
    249247         IF( ln_zps ) THEN                      ! zps-coordinate (partial steps) interpolation at the last ocean level 
    250             DO_2D( 1, 1, 1, 1 ) 
     248            DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    251249               ik = mbkt(ji,jj)  
    252250               IF( ik > 1 ) THEN 
  • NEMO/branches/2021/dev_r14122_HPC-08_Mueller_OSMOSIS_streamlining/tests/ISOMIP+/MY_SRC/eosbn2.F90

    r14822 r14863  
    256256      CASE( np_teos10, np_eos80 )                !==  polynomial TEOS-10 / EOS-80 ==! 
    257257         ! 
    258          DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     258         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    259259            ! 
    260260            zh  = pdep(ji,jj,jk) * r1_Z0                                  ! depth 
     
    292292      CASE( np_seos )                !==  simplified EOS  ==! 
    293293         ! 
    294          DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     294         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    295295            zt  = pts  (ji,jj,jk,jp_tem) - 10._wp 
    296296            zs  = pts  (ji,jj,jk,jp_sal) - 35._wp 
     
    307307      CASE( np_leos )                !==  linear ISOMIP EOS  ==! 
    308308         ! 
    309          DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     309         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    310310            zt  = pts  (ji,jj,jk,jp_tem) - (-1._wp) 
    311311            zs  = pts  (ji,jj,jk,jp_sal) - 34.2_wp 
     
    382382            END DO 
    383383            ! 
    384             DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     384            DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    385385               ! 
    386386               ! compute density (2*nn_sto_eos) times: 
     
    432432         ! Non-stochastic equation of state 
    433433         ELSE 
    434             DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     434            DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    435435               ! 
    436436               zh  = pdep(ji,jj,jk) * r1_Z0                                  ! depth 
     
    470470      CASE( np_seos )                !==  simplified EOS  ==! 
    471471         ! 
    472          DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     472         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    473473            zt  = pts  (ji,jj,jk,jp_tem) - 10._wp 
    474474            zs  = pts  (ji,jj,jk,jp_sal) - 35._wp 
     
    488488      CASE( np_leos )                !==  linear ISOMIP EOS  ==! 
    489489         ! 
    490          DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     490         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    491491            zt  = pts  (ji,jj,jk,jp_tem) - (-1._wp) 
    492492            zs  = pts  (ji,jj,jk,jp_sal) - 34.2_wp 
     
    551551      CASE( np_teos10, np_eos80 )                !==  polynomial TEOS-10 / EOS-80 ==! 
    552552         ! 
    553          DO_2D( 1, 1, 1, 1 ) 
     553         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    554554            ! 
    555555            zh  = pdep(ji,jj) * r1_Z0                                  ! depth 
     
    586586      CASE( np_seos )                !==  simplified EOS  ==! 
    587587         ! 
    588          DO_2D( 1, 1, 1, 1 ) 
     588         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    589589            ! 
    590590            zt    = pts  (ji,jj,jp_tem)  - 10._wp 
     
    602602      CASE( np_leos )                !==  ISOMIP EOS  ==! 
    603603         ! 
    604          DO_2D( 1, 1, 1, 1 ) 
     604         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    605605            ! 
    606606            zt    = pts  (ji,jj,jp_tem)  - (-1._wp) 
     
    625625 
    626626   SUBROUTINE eos_insitu_pot_2d( pts, prhop ) 
     627      !! 
     628      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   pts    ! 1 : potential temperature  [Celsius] 
     629      !                                                     ! 2 : salinity               [psu] 
     630      REAL(wp), DIMENSION(:,:)  , INTENT(  out) ::   prhop  ! potential density (surface referenced) 
     631      !! 
     632      CALL eos_insitu_pot_2d_t( pts, is_tile(pts), prhop, is_tile(prhop) ) 
     633   END SUBROUTINE eos_insitu_pot_2d 
     634 
     635 
     636   SUBROUTINE eos_insitu_pot_2d_t( pts, ktts, prhop, ktrhop ) 
    627637      !!---------------------------------------------------------------------- 
    628638      !!                  ***  ROUTINE eos_insitu_pot  *** 
     
    637647      !! 
    638648      !!---------------------------------------------------------------------- 
    639       REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) ::   pts    ! 1 : potential temperature  [Celsius] 
     649      INTEGER                              , INTENT(in   ) ::   ktts, ktrhop 
     650      REAL(wp), DIMENSION(A2D_T(ktts),JPTS), INTENT(in   ) ::   pts    ! 1 : potential temperature  [Celsius] 
    640651      !                                                                ! 2 : salinity               [psu] 
    641       REAL(wp), DIMENSION(jpi,jpj     ), INTENT(  out) ::   prhop  ! potential density (surface referenced) 
     652      REAL(wp), DIMENSION(A2D_T(ktrhop)   ), INTENT(  out) ::   prhop  ! potential density (surface referenced) 
    642653      ! 
    643654      INTEGER  ::   ji, jj, jk, jsmp             ! dummy loop indices 
     
    654665      CASE( np_teos10, np_eos80 )                !==  polynomial TEOS-10 / EOS-80 ==! 
    655666         ! 
    656             DO_2D( 1, 1, 1, 1 ) 
     667         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    657668               ! 
    658669               zt  = pts (ji,jj,jp_tem) * r1_T0                           ! temperature 
     
    675686      CASE( np_seos )                !==  simplified EOS  ==! 
    676687         ! 
    677          DO_2D( 1, 1, 1, 1 ) 
     688         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    678689            zt  = pts  (ji,jj,jp_tem) - 10._wp 
    679690            zs  = pts  (ji,jj,jp_sal) - 35._wp 
     
    689700      CASE( np_leos )                !==  ISOMIP EOS  ==! 
    690701         ! 
    691          DO_2D( 1, 1, 1, 1 ) 
     702         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    692703            ! 
    693704            zt    = pts  (ji,jj,jp_tem)  - (-1._wp) 
     
    707718      IF( ln_timing )   CALL timing_stop('eos-pot') 
    708719      ! 
    709    END SUBROUTINE eos_insitu_pot_2d 
     720   END SUBROUTINE eos_insitu_pot_2d_t 
    710721 
    711722 
     
    746757      CASE( np_teos10, np_eos80 )                !==  polynomial TEOS-10 / EOS-80 ==! 
    747758         ! 
    748          DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     759         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    749760            ! 
    750761            zh  = gdept(ji,jj,jk,Kmm) * r1_Z0                                ! depth 
     
    799810      CASE( np_seos )                  !==  simplified EOS  ==! 
    800811         ! 
    801          DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     812         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    802813            zt  = pts (ji,jj,jk,jp_tem) - 10._wp   ! pot. temperature anomaly (t-T0) 
    803814            zs  = pts (ji,jj,jk,jp_sal) - 35._wp   ! abs. salinity anomaly (s-S0) 
     
    815826      CASE( np_leos )                  !==  linear ISOMIP EOS  ==! 
    816827         ! 
    817          DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     828         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    818829            zt  = pts (ji,jj,jk,jp_tem) - (-1._wp) 
    819830            zs  = pts (ji,jj,jk,jp_sal) - 34.2_wp   ! abs. salinity anomaly (s-S0) 
     
    881892      CASE( np_teos10, np_eos80 )                !==  polynomial TEOS-10 / EOS-80 ==! 
    882893         ! 
    883          DO_2D( 1, 1, 1, 1 ) 
     894         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    884895            ! 
    885896            zh  = pdep(ji,jj) * r1_Z0                                  ! depth 
     
    934945      CASE( np_seos )                  !==  simplified EOS  ==! 
    935946         ! 
    936          DO_2D( 1, 1, 1, 1 ) 
     947         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    937948            ! 
    938949            zt    = pts  (ji,jj,jp_tem) - 10._wp   ! pot. temperature anomaly (t-T0) 
     
    950961      CASE( np_leos )                  !==  linear ISOMIP EOS  ==! 
    951962         ! 
    952          DO_2D( 1, 1, 1, 1 ) 
     963         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    953964            ! 
    954965            zt    = pts  (ji,jj,jp_tem) - (-1._wp)   ! pot. temperature anomaly (t-T0) 
     
    11241135      IF( ln_timing )   CALL timing_start('bn2') 
    11251136      ! 
    1126       DO_3D( 1, 1, 1, 1, 2, jpkm1 )      ! interior points only (2=< jk =< jpkm1 ); surface and bottom value set to zero one for all in istate.F90 
     1137      DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 2, jpkm1 )      ! interior points only (2=< jk =< jpkm1 ); surface and bottom value set to zero one for all in istate.F90 
    11271138         zrw =   ( gdepw(ji,jj,jk  ,Kmm) - gdept(ji,jj,jk,Kmm) )   & 
    11281139            &  / ( gdept(ji,jj,jk-1,Kmm) - gdept(ji,jj,jk,Kmm) )  
     
    14181429      CASE( np_leos )                !==  linear ISOMIP EOS  ==! 
    14191430         ! 
    1420          DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     1431         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    14211432            zt  = pts(ji,jj,jk,jp_tem) - (-1._wp)  ! temperature anomaly (t-T0) 
    14221433            zs = pts (ji,jj,jk,jp_sal) - 34.2_wp   ! abs. salinity anomaly (s-S0) 
  • NEMO/branches/2021/dev_r14122_HPC-08_Mueller_OSMOSIS_streamlining/tests/ISOMIP+/MY_SRC/istate.F90

    r14053 r14863  
    167167      ! 
    168168!!gm  the use of umsak & vmask is not necessary below as uu(:,:,:,Kmm), vv(:,:,:,Kmm), uu(:,:,:,Kbb), vv(:,:,:,Kbb) are always masked 
    169       DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     169      DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 ) 
    170170         uu_b(ji,jj,Kmm) = uu_b(ji,jj,Kmm) + e3u(ji,jj,jk,Kmm) * uu(ji,jj,jk,Kmm) * umask(ji,jj,jk) 
    171171         vv_b(ji,jj,Kmm) = vv_b(ji,jj,Kmm) + e3v(ji,jj,jk,Kmm) * vv(ji,jj,jk,Kmm) * vmask(ji,jj,jk) 
  • NEMO/branches/2021/dev_r14122_HPC-08_Mueller_OSMOSIS_streamlining/tests/OVERFLOW/MY_SRC/usrdef_zgr.F90

    r14822 r14863  
    184184            pe3vw(:,:,jk) = pe3w_1d (jk) 
    185185         END DO 
    186          DO_2D( 1, 1, 1, 1 ) 
     186         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    187187            ik = k_bot(ji,jj) 
    188188            pdepw(ji,jj,ik+1) = MIN( zht(ji,jj) , pdepw_1d(ik+1) ) 
  • NEMO/branches/2021/dev_r14122_HPC-08_Mueller_OSMOSIS_streamlining/tests/SWG/MY_SRC/usrdef_hgr.F90

    r13752 r14863  
    113113      DO jj = 1, jpj  
    114114         DO ji = 1, jpi  
    115             zim1 = REAL( ji + nimpp - 1 )   ;   zim05 = REAL( ji + nimpp - 1 ) - 0.5  
    116             zjm1 = REAL( jj + njmpp - 1 )   ;   zjm05 = REAL( jj + njmpp - 1 ) - 0.5  
     115            zim1 = REAL( ji + nimpp - nn_hls )   ;   zim05 = REAL( ji + nimpp - nn_hls ) - 0.5 
     116            zjm1 = REAL( jj + njmpp - nn_hls )   ;   zjm05 = REAL( jj + njmpp - nn_hls ) - 0.5 
    117117            !    
    118118            !glamt(i,j) position (meters) at T-point  
  • NEMO/branches/2021/dev_r14122_HPC-08_Mueller_OSMOSIS_streamlining/tests/VORTEX/MY_SRC/usrdef_istate.F90

    r14822 r14863  
    7676      ! 
    7777      ! temperature:          
    78       DO_2D( 1, 1, 1, 1 ) 
     78      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    7979         zx = glamt(ji,jj) * 1.e3 
    8080         zy = gphit(ji,jj) * 1.e3 
     
    160160      ! Sea level: 
    161161      za = -zP0 * (1._wp-EXP(-zH)) / (grav*(zH-1._wp + EXP(-zH))) 
    162       DO_2D( 1, 1, 1, 1 ) 
     162      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    163163         zx = glamt(ji,jj) * 1.e3 
    164164         zy = gphit(ji,jj) * 1.e3 
Note: See TracChangeset for help on using the changeset viewer.