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 14856 for NEMO/branches/2021/dev_r14122_HPC-08_Mueller_OSMOSIS_streamlining/src/OCE/TRA/trasbc.F90 – NEMO

Ignore:
Timestamp:
2021-05-12T17:58:07+02:00 (3 years ago)
Author:
smueller
Message:

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

File:
1 edited

Legend:

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

    r14822 r14856  
    7777      ! 
    7878      INTEGER  ::   ji, jj, jk, jn               ! dummy loop indices 
    79       INTEGER  ::   ikt, ikb, isi, iei, isj, iej ! local integers 
     79      INTEGER  ::   ikt, ikb                    ! local integers 
    8080      REAL(wp) ::   zfact, z1_e3t, zdep, ztim    ! local scalar 
    8181      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::  ztrdt, ztrds 
     
    8484      IF( ln_timing )   CALL timing_start('tra_sbc') 
    8585      ! 
    86       IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
     86      IF( .NOT. l_istiled .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    8787         IF( kt == nit000 ) THEN 
    8888            IF(lwp) WRITE(numout,*) 
     
    9898      ENDIF 
    9999      ! 
    100       IF( ntsi == Nis0 ) THEN ; isi = nn_hls ; ELSE ; isi = 0 ; ENDIF    ! Avoid double-counting when using tiling 
    101       IF( ntsj == Njs0 ) THEN ; isj = nn_hls ; ELSE ; isj = 0 ; ENDIF 
    102       IF( ntei == Nie0 ) THEN ; iei = nn_hls ; ELSE ; iei = 0 ; ENDIF 
    103       IF( ntej == Nje0 ) THEN ; iej = nn_hls ; ELSE ; iej = 0 ; ENDIF 
    104  
    105100!!gm  This should be moved into sbcmod.F90 module ? (especially now that ln_traqsr is read in namsbc namelist) 
    106101      IF( .NOT.ln_traqsr ) THEN     ! no solar radiation penetration 
    107          DO_2D( isi, iei, isj, iej ) 
     102         DO_2D_OVR( nn_hls, nn_hls, nn_hls, nn_hls ) 
    108103            qns(ji,jj) = qns(ji,jj) + qsr(ji,jj)      ! total heat flux in qns 
    109104            qsr(ji,jj) = 0._wp                        ! qsr set to zero 
     
    118113         IF( ln_rstart .AND. .NOT.l_1st_euler ) THEN      ! Restart: read in restart file 
    119114            zfact = 0.5_wp 
    120             IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
     115            IF( .NOT. l_istiled .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    121116               IF(lwp) WRITE(numout,*) '          nit000-1 sbc tracer content field read in the restart file' 
    122117               sbc_tsc(:,:,:) = 0._wp 
     
    126121         ELSE                                             ! No restart or restart not found: Euler forward time stepping 
    127122            zfact = 1._wp 
    128             DO_2D( isi, iei, isj, iej ) 
     123            DO_2D_OVR( nn_hls, nn_hls, nn_hls, nn_hls ) 
    129124               sbc_tsc(ji,jj,:) = 0._wp 
    130125               sbc_tsc_b(ji,jj,:) = 0._wp 
     
    133128      ELSE                                !* other time-steps: swap of forcing fields 
    134129         zfact = 0.5_wp 
    135          DO_2D( isi, iei, isj, iej ) 
     130         DO_2D_OVR( nn_hls, nn_hls, nn_hls, nn_hls ) 
    136131            sbc_tsc_b(ji,jj,:) = sbc_tsc(ji,jj,:) 
    137132         END_2D 
    138133      ENDIF 
    139134      !                             !==  Now sbc tracer content fields  ==! 
    140       DO_2D( isi, iei, isj, iej ) 
     135      DO_2D_OVR( nn_hls, nn_hls, nn_hls, nn_hls ) 
    141136         sbc_tsc(ji,jj,jp_tem) = r1_rho0_rcp * qns(ji,jj)   ! non solar heat flux 
    142137         sbc_tsc(ji,jj,jp_sal) = r1_rho0     * sfx(ji,jj)   ! salt flux due to freezing/melting 
    143138      END_2D 
    144139      IF( ln_linssh ) THEN                !* linear free surface 
    145          DO_2D( isi, iei, isj, iej )                    !==>> add concentration/dilution effect due to constant volume cell 
     140         DO_2D_OVR( nn_hls, nn_hls, nn_hls, nn_hls )                    !==>> add concentration/dilution effect due to constant volume cell 
    146141            sbc_tsc(ji,jj,jp_tem) = sbc_tsc(ji,jj,jp_tem) + r1_rho0 * emp(ji,jj) * pts(ji,jj,1,jp_tem,Kmm) 
    147142            sbc_tsc(ji,jj,jp_sal) = sbc_tsc(ji,jj,jp_sal) + r1_rho0 * emp(ji,jj) * pts(ji,jj,1,jp_sal,Kmm) 
    148143         END_2D                                 !==>> output c./d. term 
    149          IF( ntile == 0 .OR. ntile == nijtile )  THEN             ! Do only on the last tile 
    150             IF( iom_use('emp_x_sst') )   CALL iom_put( "emp_x_sst", emp (:,:) * pts(:,:,1,jp_tem,Kmm) ) 
    151             IF( iom_use('emp_x_sss') )   CALL iom_put( "emp_x_sss", emp (:,:) * pts(:,:,1,jp_sal,Kmm) ) 
    152          ENDIF 
     144         IF( iom_use('emp_x_sst') )   CALL iom_put( "emp_x_sst", emp (:,:) * pts(:,:,1,jp_tem,Kmm) ) 
     145         IF( iom_use('emp_x_sss') )   CALL iom_put( "emp_x_sss", emp (:,:) * pts(:,:,1,jp_sal,Kmm) ) 
    153146      ENDIF 
    154147      ! 
     
    160153      END DO 
    161154      ! 
    162       IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only on the last tile 
     155      IF( .NOT. l_istiled .OR. ntile == nijtile )  THEN                ! Do only on the last tile 
    163156         IF( lrst_oce ) THEN           !==  write sbc_tsc in the ocean restart file  ==! 
    164157            CALL iom_rstput( kt, nitrst, numrow, 'sbc_hc_b', sbc_tsc(:,:,jp_tem) ) 
     
    186179      ENDIF 
    187180 
    188       IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only on the last tile 
    189          IF( iom_use('rnf_x_sst') )   CALL iom_put( "rnf_x_sst", rnf*pts(:,:,1,jp_tem,Kmm) )   ! runoff term on sst 
    190          IF( iom_use('rnf_x_sss') )   CALL iom_put( "rnf_x_sss", rnf*pts(:,:,1,jp_sal,Kmm) )   ! runoff term on sss 
    191       ENDIF 
     181      IF( iom_use('rnf_x_sst') )   CALL iom_put( "rnf_x_sst", rnf*pts(:,:,1,jp_tem,Kmm) )   ! runoff term on sst 
     182      IF( iom_use('rnf_x_sss') )   CALL iom_put( "rnf_x_sss", rnf*pts(:,:,1,jp_sal,Kmm) )   ! runoff term on sss 
    192183 
    193184#if defined key_asminc 
Note: See TracChangeset for help on using the changeset viewer.