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

Changeset 14607


Ignore:
Timestamp:
2021-03-11T13:37:58+01:00 (3 years ago)
Author:
hadcv
Message:

#2600: Changes for XIOS development

Location:
NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/DIA/diaar5.F90

    r14072 r14607  
    3434   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:  ) ::   thick0       ! ocean thickness (interior domain) 
    3535   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sn0          ! initial salinity 
    36    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   hstr_adv, hstr_ldf 
    3736 
    3837   LOGICAL  :: l_ar5 
     
    5554      !!---------------------------------------------------------------------- 
    5655      ! 
    57       ALLOCATE( thick0(jpi,jpj) , sn0(jpi,jpj,jpk) , & 
    58          &      hstr_adv(jpi,jpj,jpts,2), hstr_ldf(jpi,jpj,jpts,2), STAT=dia_ar5_alloc ) 
     56      ALLOCATE( thick0(jpi,jpj) , sn0(jpi,jpj,jpk), STAT=dia_ar5_alloc ) 
    5957      ! 
    6058      CALL mpp_sum ( 'diaar5', dia_ar5_alloc ) 
     
    306304   END SUBROUTINE dia_ar5 
    307305 
    308    ! TEMP: [tiling] These changes not necessary if using XIOS (subdomain support, will not output haloes) 
     306 
    309307   SUBROUTINE dia_ar5_hst( ktra, cptr, puflx, pvflx ) 
    310308      !!---------------------------------------------------------------------- 
     
    320318      ! 
    321319      INTEGER    ::  ji, jj, jk 
    322  
    323       IF( cptr /= 'adv' .AND. cptr /= 'ldf' ) RETURN 
    324       IF( ktra /= jp_tem .AND. ktra /= jp_sal ) RETURN 
     320      REAL(wp), DIMENSION(A2D(nn_hls))  :: z2d 
     321 
     322      z2d(:,:) = puflx(:,:,1) 
     323      DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
     324         z2d(ji,jj) = z2d(ji,jj) + puflx(ji,jj,jk) 
     325      END_3D 
    325326 
    326327      IF( cptr == 'adv' ) THEN 
    327          DO_2D( 0, 0, 0, 0 ) 
    328             hstr_adv(ji,jj,ktra,1) = puflx(ji,jj,1) 
    329             hstr_adv(ji,jj,ktra,2) = pvflx(ji,jj,1) 
    330          END_2D 
    331          DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
    332             hstr_adv(ji,jj,ktra,1) = hstr_adv(ji,jj,ktra,1) + puflx(ji,jj,jk) 
    333             hstr_adv(ji,jj,ktra,2) = hstr_adv(ji,jj,ktra,2) + pvflx(ji,jj,jk) 
    334          END_3D 
     328         IF( ktra == jp_tem ) CALL iom_put( 'uadv_heattr' , rho0_rcp * z2d(:,:) )  ! advective heat transport in i-direction 
     329         IF( ktra == jp_sal ) CALL iom_put( 'uadv_salttr' , rho0     * z2d(:,:) )  ! advective salt transport in i-direction 
    335330      ELSE IF( cptr == 'ldf' ) THEN 
    336          DO_2D( 0, 0, 0, 0 ) 
    337             hstr_ldf(ji,jj,ktra,1) = puflx(ji,jj,1) 
    338             hstr_ldf(ji,jj,ktra,2) = pvflx(ji,jj,1) 
    339          END_2D 
    340          DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
    341             hstr_ldf(ji,jj,ktra,1) = hstr_ldf(ji,jj,ktra,1) + puflx(ji,jj,jk) 
    342             hstr_ldf(ji,jj,ktra,2) = hstr_ldf(ji,jj,ktra,2) + pvflx(ji,jj,jk) 
    343          END_3D 
    344       ENDIF 
    345  
    346       IF( ntile == 0 .OR. ntile == nijtile ) THEN 
    347          IF( cptr == 'adv' ) THEN 
    348             IF( ktra == jp_tem ) CALL iom_put( 'uadv_heattr' , rho0_rcp * hstr_adv(:,:,ktra,1) )  ! advective heat transport in i-direction 
    349             IF( ktra == jp_sal ) CALL iom_put( 'uadv_salttr' , rho0     * hstr_adv(:,:,ktra,1) )  ! advective salt transport in i-direction 
    350             IF( ktra == jp_tem ) CALL iom_put( 'vadv_heattr' , rho0_rcp * hstr_adv(:,:,ktra,2) )  ! advective heat transport in j-direction 
    351             IF( ktra == jp_sal ) CALL iom_put( 'vadv_salttr' , rho0     * hstr_adv(:,:,ktra,2) )  ! advective salt transport in j-direction 
    352          ENDIF 
    353          IF( cptr == 'ldf' ) THEN 
    354             IF( ktra == jp_tem ) CALL iom_put( 'udiff_heattr' , rho0_rcp * hstr_ldf(:,:,ktra,1) ) ! diffusive heat transport in i-direction 
    355             IF( ktra == jp_sal ) CALL iom_put( 'udiff_salttr' , rho0     * hstr_ldf(:,:,ktra,1) ) ! diffusive salt transport in i-direction 
    356             IF( ktra == jp_tem ) CALL iom_put( 'vdiff_heattr' , rho0_rcp * hstr_ldf(:,:,ktra,2) ) ! diffusive heat transport in j-direction 
    357             IF( ktra == jp_sal ) CALL iom_put( 'vdiff_salttr' , rho0     * hstr_ldf(:,:,ktra,2) ) ! diffusive salt transport in j-direction 
    358          ENDIF 
     331         IF( ktra == jp_tem ) CALL iom_put( 'udiff_heattr' , rho0_rcp * z2d(:,:) ) ! diffusive heat transport in i-direction 
     332         IF( ktra == jp_sal ) CALL iom_put( 'udiff_salttr' , rho0     * z2d(:,:) ) ! diffusive salt transport in i-direction 
     333      ENDIF 
     334      ! 
     335      z2d(:,:) = pvflx(:,:,1) 
     336      DO_3D( 0, 0, 0, 0, 1, jpkm1 ) 
     337         z2d(ji,jj) = z2d(ji,jj) + pvflx(ji,jj,jk) 
     338      END_3D 
     339 
     340      IF( cptr == 'adv' ) THEN 
     341         IF( ktra == jp_tem ) CALL iom_put( 'vadv_heattr' , rho0_rcp * z2d(:,:) )  ! advective heat transport in j-direction 
     342         IF( ktra == jp_sal ) CALL iom_put( 'vadv_salttr' , rho0     * z2d(:,:) )  ! advective salt transport in j-direction 
     343      ELSE IF( cptr == 'ldf' ) THEN 
     344         IF( ktra == jp_tem ) CALL iom_put( 'vdiff_heattr' , rho0_rcp * z2d(:,:) ) ! diffusive heat transport in j-direction 
     345         IF( ktra == jp_sal ) CALL iom_put( 'vdiff_salttr' , rho0     * z2d(:,:) ) ! diffusive salt transport in j-direction 
    359346      ENDIF 
    360347 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/DOM/domutl.F90

    r14072 r14607  
    2222 
    2323   INTERFACE is_tile 
    24       MODULE PROCEDURE is_tile_2d, is_tile_3d, is_tile_4d 
     24      MODULE PROCEDURE is_tile_2d_sp, is_tile_3d_sp, is_tile_4d_sp, is_tile_2d_dp, is_tile_3d_dp, is_tile_4d_dp 
    2525   END INTERFACE is_tile 
    2626 
     
    116116 
    117117 
    118    FUNCTION is_tile_2d( pt ) 
    119       !! 
    120       REAL(wp), DIMENSION(:,:), INTENT(in) ::   pt 
    121       INTEGER :: is_tile_2d 
    122       !! 
    123       IF( ln_tile .AND. (SIZE(pt, 1) < jpi .OR. SIZE(pt, 2) < jpj) ) THEN 
    124          is_tile_2d = 1 
     118   ! TODO: Move these into domtile 
     119   INTEGER FUNCTION is_tile_2d_sp( pt ) 
     120      REAL(sp), DIMENSION(:,:), INTENT(in) ::   pt 
     121 
     122      IF( l_istiled .AND. (SIZE(pt, 1) < jpi .OR. SIZE(pt, 2) < jpj) ) THEN 
     123         is_tile_2d_sp = 1 
    125124      ELSE 
    126          is_tile_2d = 0 
     125         is_tile_2d_sp = 0 
    127126      ENDIF 
    128    END FUNCTION is_tile_2d 
     127   END FUNCTION is_tile_2d_sp 
    129128 
    130129 
    131    FUNCTION is_tile_3d( pt ) 
    132       !! 
    133       REAL(wp), DIMENSION(:,:,:), INTENT(in) ::   pt 
    134       INTEGER :: is_tile_3d 
    135       !! 
    136       IF( ln_tile .AND. (SIZE(pt, 1) < jpi .OR. SIZE(pt, 2) < jpj) ) THEN 
    137          is_tile_3d = 1 
     130   INTEGER FUNCTION is_tile_2d_dp( pt ) 
     131      REAL(dp), DIMENSION(:,:), INTENT(in) ::   pt 
     132 
     133      IF( l_istiled .AND. (SIZE(pt, 1) < jpi .OR. SIZE(pt, 2) < jpj) ) THEN 
     134         is_tile_2d_dp = 1 
    138135      ELSE 
    139          is_tile_3d = 0 
     136         is_tile_2d_dp = 0 
    140137      ENDIF 
    141    END FUNCTION is_tile_3d 
     138   END FUNCTION is_tile_2d_dp 
    142139 
    143140 
    144    FUNCTION is_tile_4d( pt ) 
    145       !! 
    146       REAL(wp), DIMENSION(:,:,:,:), INTENT(in) ::   pt 
    147       INTEGER :: is_tile_4d 
    148       !! 
    149       IF( ln_tile .AND. (SIZE(pt, 1) < jpi .OR. SIZE(pt, 2) < jpj) ) THEN 
    150          is_tile_4d = 1 
     141   INTEGER FUNCTION is_tile_3d_sp( pt ) 
     142      REAL(sp), DIMENSION(:,:,:), INTENT(in) ::   pt 
     143 
     144      IF( l_istiled .AND. (SIZE(pt, 1) < jpi .OR. SIZE(pt, 2) < jpj) ) THEN 
     145         is_tile_3d_sp = 1 
    151146      ELSE 
    152          is_tile_4d = 0 
     147         is_tile_3d_sp = 0 
    153148      ENDIF 
    154    END FUNCTION is_tile_4d 
     149   END FUNCTION is_tile_3d_sp 
    155150 
     151 
     152   INTEGER FUNCTION is_tile_3d_dp( pt ) 
     153      REAL(dp), DIMENSION(:,:,:), INTENT(in) ::   pt 
     154 
     155      IF( l_istiled .AND. (SIZE(pt, 1) < jpi .OR. SIZE(pt, 2) < jpj) ) THEN 
     156         is_tile_3d_dp = 1 
     157      ELSE 
     158         is_tile_3d_dp = 0 
     159      ENDIF 
     160   END FUNCTION is_tile_3d_dp 
     161 
     162 
     163   INTEGER FUNCTION is_tile_4d_sp( pt ) 
     164      REAL(sp), DIMENSION(:,:,:,:), INTENT(in) ::   pt 
     165 
     166      IF( l_istiled .AND. (SIZE(pt, 1) < jpi .OR. SIZE(pt, 2) < jpj) ) THEN 
     167         is_tile_4d_sp = 1 
     168      ELSE 
     169         is_tile_4d_sp = 0 
     170      ENDIF 
     171   END FUNCTION is_tile_4d_sp 
     172 
     173 
     174   INTEGER FUNCTION is_tile_4d_dp( pt ) 
     175      REAL(dp), DIMENSION(:,:,:,:), INTENT(in) ::   pt 
     176 
     177      IF( l_istiled .AND. (SIZE(pt, 1) < jpi .OR. SIZE(pt, 2) < jpj) ) THEN 
     178         is_tile_4d_dp = 1 
     179      ELSE 
     180         is_tile_4d_dp = 0 
     181      ENDIF 
     182   END FUNCTION is_tile_4d_dp 
    156183   !!====================================================================== 
    157184END MODULE domutl 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/IOM/iom.F90

    r14239 r14607  
    20142014      IF( iom_use(cdname) ) THEN 
    20152015#if defined key_xios 
    2016          CALL xios_send_field( cdname, pfield2d ) 
     2016         IF( is_tile(pfield2d) == 1 ) THEN 
     2017            CALL xios_send_field( cdname, pfield2d, ntile - 1 ) 
     2018         ELSE IF( .NOT. l_istiled .OR. ntile == nijtile ) THEN 
     2019            CALL xios_send_field( cdname, pfield2d ) 
     2020         ENDIF 
    20172021#else 
    20182022         WRITE(numout,*) pfield2d   ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings 
     
    20262030      IF( iom_use(cdname) ) THEN 
    20272031#if defined key_xios 
    2028          CALL xios_send_field( cdname, pfield2d ) 
     2032         IF( is_tile(pfield2d) == 1 ) THEN 
     2033            CALL xios_send_field( cdname, pfield2d, ntile - 1 ) 
     2034         ELSE IF( .NOT. l_istiled .OR. ntile == nijtile ) THEN 
     2035            CALL xios_send_field( cdname, pfield2d ) 
     2036         ENDIF 
    20292037#else 
    20302038         WRITE(numout,*) pfield2d   ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings 
     
    20382046      IF( iom_use(cdname) ) THEN 
    20392047#if defined key_xios 
    2040          CALL xios_send_field( cdname, pfield3d ) 
     2048         IF( is_tile(pfield3d) == 1 ) THEN 
     2049            CALL xios_send_field( cdname, pfield3d, ntile - 1 ) 
     2050         ELSE IF( .NOT. l_istiled .OR. ntile == nijtile ) THEN 
     2051            CALL xios_send_field( cdname, pfield3d ) 
     2052         ENDIF 
    20412053#else 
    20422054         WRITE(numout,*) pfield3d   ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings 
     
    20502062      IF( iom_use(cdname) ) THEN 
    20512063#if defined key_xios 
    2052          CALL xios_send_field( cdname, pfield3d ) 
     2064         IF( is_tile(pfield3d) == 1 ) THEN 
     2065            CALL xios_send_field( cdname, pfield3d, ntile - 1 ) 
     2066         ELSE IF( .NOT. l_istiled .OR. ntile == nijtile ) THEN 
     2067            CALL xios_send_field( cdname, pfield3d ) 
     2068         ENDIF 
    20532069#else 
    20542070         WRITE(numout,*) pfield3d   ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings 
     
    20622078      IF( iom_use(cdname) ) THEN 
    20632079#if defined key_xios 
    2064          CALL xios_send_field (cdname, pfield4d ) 
     2080         IF( is_tile(pfield4d) == 1 ) THEN 
     2081            CALL xios_send_field( cdname, pfield4d, ntile - 1 ) 
     2082         ELSE IF( .NOT. l_istiled .OR. ntile == nijtile ) THEN 
     2083            CALL xios_send_field( cdname, pfield4d ) 
     2084         ENDIF 
    20652085#else 
    20662086         WRITE(numout,*) pfield4d   ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings 
     
    20742094      IF( iom_use(cdname) ) THEN 
    20752095#if defined key_xios 
    2076          CALL xios_send_field (cdname, pfield4d ) 
     2096         IF( is_tile(pfield4d) == 1 ) THEN 
     2097            CALL xios_send_field( cdname, pfield4d, ntile - 1 ) 
     2098         ELSE IF( .NOT. l_istiled .OR. ntile == nijtile ) THEN 
     2099            CALL xios_send_field( cdname, pfield4d ) 
     2100         ENDIF 
    20772101#else 
    20782102         WRITE(numout,*) pfield4d   ! iom_use(cdname) = .F. -> useless test to avoid compilation warnings 
     
    20882112   SUBROUTINE iom_set_domain_attr( cdid, ni_glo, nj_glo, ibegin, jbegin, ni, nj,                                               & 
    20892113      &                                    data_dim, data_ibegin, data_ni, data_jbegin, data_nj, lonvalue, latvalue, mask,     & 
     2114      &                                  ntiles, tile_ibegin, tile_jbegin, tile_ni, tile_nj,                                   & 
     2115      &                                  tile_data_ibegin, tile_data_jbegin, tile_data_ni, tile_data_nj,                       & 
    20902116      &                                    nvertex, bounds_lon, bounds_lat, area ) 
    20912117      !!---------------------------------------------------------------------- 
     
    20932119      CHARACTER(LEN=*)                  , INTENT(in) ::   cdid 
    20942120      INTEGER                 , OPTIONAL, INTENT(in) ::   ni_glo, nj_glo, ibegin, jbegin, ni, nj 
     2121      INTEGER,  DIMENSION(:)  , OPTIONAL, INTENT(in) ::   tile_ibegin, tile_jbegin, tile_ni, tile_nj 
     2122      INTEGER,  DIMENSION(:)  , OPTIONAL, INTENT(in) ::   tile_data_ibegin, tile_data_jbegin, tile_data_ni, tile_data_nj 
    20952123      INTEGER                 , OPTIONAL, INTENT(in) ::   data_dim, data_ibegin, data_ni, data_jbegin, data_nj 
    2096       INTEGER                 , OPTIONAL, INTENT(in) ::   nvertex 
     2124      INTEGER                 , OPTIONAL, INTENT(in) ::   nvertex, ntiles 
    20972125      REAL(dp), DIMENSION(:)  , OPTIONAL, INTENT(in) ::   lonvalue, latvalue 
    20982126      REAL(dp), DIMENSION(:,:), OPTIONAL, INTENT(in) ::   bounds_lon, bounds_lat, area 
     
    21032131         CALL xios_set_domain_attr     ( cdid, ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj,   & 
    21042132            &    data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj ,   & 
     2133            &    ntiles=ntiles, tile_ibegin=tile_ibegin, tile_jbegin=tile_jbegin, tile_ni=tile_ni, tile_nj=tile_nj,        & 
     2134            &    tile_data_ibegin=tile_data_ibegin, tile_data_jbegin=tile_data_jbegin,                                     & 
     2135            &    tile_data_ni=tile_data_ni, tile_data_nj=tile_data_nj,                                                     & 
    21052136            &    lonvalue_1D=lonvalue, latvalue_1D=latvalue, mask_1D=mask, nvertex=nvertex, bounds_lon_1D=bounds_lon,      & 
    21062137            &    bounds_lat_1D=bounds_lat, area=area, type='curvilinear') 
     
    21092140         CALL xios_set_domaingroup_attr( cdid, ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj,   & 
    21102141            &    data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj ,   & 
     2142            &    ntiles=ntiles, tile_ibegin=tile_ibegin, tile_jbegin=tile_jbegin, tile_ni=tile_ni, tile_nj=tile_nj,        & 
     2143            &    tile_data_ibegin=tile_data_ibegin, tile_data_jbegin=tile_data_jbegin,                                     & 
     2144            &    tile_data_ni=tile_data_ni, tile_data_nj=tile_data_nj,                                                     & 
    21112145            &    lonvalue_1D=lonvalue, latvalue_1D=latvalue, mask_1D=mask, nvertex=nvertex, bounds_lon_1D=bounds_lon,      & 
    21122146            &    bounds_lat_1D=bounds_lat, area=area, type='curvilinear' ) 
     
    22762310      ! 
    22772311      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zmask 
     2312      INTEGER :: jn 
     2313      INTEGER, DIMENSION(nijtile) :: ini, inj, idb 
    22782314      LOGICAL, INTENT(IN) :: ldxios, ldrxios 
    22792315      !!---------------------------------------------------------------------- 
     
    22812317      CALL iom_set_domain_attr("grid_"//cdgrd, ni_glo=Ni0glo,nj_glo=Nj0glo,ibegin=mig0(Nis0)-1,jbegin=mjg0(Njs0)-1,ni=Ni_0,nj=Nj_0) 
    22822318      CALL iom_set_domain_attr("grid_"//cdgrd, data_dim=2, data_ibegin = -nn_hls, data_ni=jpi, data_jbegin = -nn_hls, data_nj=jpj) 
     2319 
     2320      IF( ln_tile ) THEN 
     2321         DO jn = 1, nijtile 
     2322            ini(jn) = ntei_a(jn) - ntsi_a(jn) + 1     ! Tile size in i and j 
     2323            inj(jn) = ntej_a(jn) - ntsj_a(jn) + 1 
     2324            idb(jn) = -nn_hls                         ! Tile data offset (halo size) 
     2325         END DO 
     2326 
     2327         ! Tile_[ij]begin are defined with respect to the processor data domain, so data_[ij]begin is added 
     2328         CALL iom_set_domain_attr("grid_"//cdgrd, ntiles=nijtile,                                     & 
     2329            & tile_ibegin=ntsi_a(1:nijtile) + idb(:) - 1, tile_jbegin=ntsj_a(1:nijtile) + idb(:) - 1, & 
     2330            & tile_ni=ini(:), tile_nj=inj(:),                                                         & 
     2331            & tile_data_ibegin=idb(:), tile_data_jbegin=idb(:),                                       & 
     2332            & tile_data_ni=ini(:) - 2 * idb(:), tile_data_nj=inj(:) - 2 * idb(:)) 
     2333      ENDIF 
     2334 
    22832335!don't define lon and lat for restart reading context. 
    22842336      IF ( .NOT.ldrxios ) & 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/TRA/trabbc.F90

    r14072 r14607  
    102102      ENDIF 
    103103      ! 
    104       IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    105          CALL iom_put ( "hfgeou" , rho0_rcp * qgh_trd0(:,:) ) 
    106       ENDIF 
     104      CALL iom_put ( "hfgeou" , rho0_rcp * qgh_trd0(:,:) ) 
     105 
    107106      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbc  - Ta: ', mask1=tmask, clinfo3='tra-ta' ) 
    108107      ! 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/TRA/trabbl.F90

    r14574 r14607  
    126126         CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' bbl_ldf  - Ta: ', mask1=tmask, & 
    127127            &          tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=           ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    128          IF( ntile == 0 .OR. ntile == nijtile ) THEN                       ! Do only on the last tile 
    129128         CALL iom_put( "ahu_bbl", ahu_bbl )   ! bbl diffusive flux i-coef 
    130129         CALL iom_put( "ahv_bbl", ahv_bbl )   ! bbl diffusive flux j-coef 
    131          ENDIF 
    132130         ! 
    133131      ENDIF 
     
    142140            ! lateral boundary conditions ; just need for outputs 
    143141            CALL lbc_lnk( 'trabbl', utr_bbl, 'U', 1.0_wp , vtr_bbl, 'V', 1.0_wp ) 
     142         ENDIF 
    144143         CALL iom_put( "uoce_bbl", utr_bbl )  ! bbl i-transport 
    145144         CALL iom_put( "voce_bbl", vtr_bbl )  ! bbl j-transport 
    146          ENDIF 
    147145         ! 
    148146      ENDIF 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/TRA/tramle.F90

    r14576 r14607  
    9696      REAL(wp) ::   zcvw, zmvw          !   -      - 
    9797      INTEGER , DIMENSION(A2D(nn_hls))     :: inml_mle 
    98       REAL(wp), DIMENSION(A2D(nn_hls))     :: zpsim_u, zpsim_v, zmld, zbm, zhu, zhv, zn2, zLf_MH 
     98      REAL(wp), DIMENSION(A2D(nn_hls))     :: zpsim_u, zpsim_v, zmld, zbm, zhu, zhv, zn2, zLf_NH, zLf_MH 
    9999      REAL(wp), DIMENSION(A2D(nn_hls),jpk) :: zpsi_uw, zpsi_vw 
    100       ! TEMP: [tiling] These changes not necessary if using XIOS (subdomain support) 
    101       REAL(wp), DIMENSION(:,:),   ALLOCATABLE, SAVE :: zLf_NH 
    102       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE :: zpsiu_mle, zpsiv_mle 
    103100      !!---------------------------------------------------------------------- 
    104101      ! 
     
    282279      END DO 
    283280 
    284       ! TEMP: [tiling] These changes not necessary if using XIOS (subdomain support) 
    285281      IF( cdtype == 'TRA') THEN              !==  outputs  ==! 
    286          IF( ntile == 0 .OR. ntile == 1 ) THEN                             ! Do only on the first tile 
    287             ALLOCATE( zLf_NH(jpi,jpj), zpsiu_mle(jpi,jpj,jpk), zpsiv_mle(jpi,jpj,jpk) ) 
    288             zpsiu_mle(:,:,:) = 0._wp ; zpsiv_mle(:,:,:) = 0._wp 
    289          ENDIF 
    290282         ! 
    291283         IF (ln_osm_mle.and.ln_zdfosm) THEN 
     
    301293         ENDIF 
    302294         ! 
     295         CALL iom_put( "Lf_NHpf" , zLf_NH  )    ! Lf = N H / f 
     296         ! 
    303297         ! divide by cross distance to give streamfunction with dimensions m^2/s 
    304          ! [comm_cleanup] ! DO_3D( 0, 0, 0, 0, 1, ikmax+1 ) 
    305          DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 1, ikmax+1 ) 
    306             zpsiu_mle(ji,jj,jk) = zpsi_uw(ji,jj,jk) * r1_e2u(ji,jj) 
    307             zpsiv_mle(ji,jj,jk) = zpsi_vw(ji,jj,jk) * r1_e1v(ji,jj) 
     298         DO_3D( 0, 0, 0, 0, 1, ikmax+1 ) 
     299            zpsi_uw(ji,jj,jk) = zpsi_uw(ji,jj,jk) * r1_e2u(ji,jj) 
     300            zpsi_vw(ji,jj,jk) = zpsi_vw(ji,jj,jk) * r1_e1v(ji,jj) 
    308301         END_3D 
    309  
    310          IF( ntile == 0 .OR. ntile == nijtile ) THEN                       ! Do only on the last tile 
    311             CALL iom_put( "Lf_NHpf" , zLf_NH  )    ! Lf = N H / f 
    312             CALL iom_put( "psiu_mle", zpsiu_mle )    ! i-mle streamfunction 
    313             CALL iom_put( "psiv_mle", zpsiv_mle )    ! j-mle streamfunction 
    314             DEALLOCATE( zLf_NH, zpsiu_mle, zpsiv_mle ) 
    315          ENDIF 
     302         CALL iom_put( "psiu_mle", zpsi_uw )    ! i-mle streamfunction 
     303         CALL iom_put( "psiv_mle", zpsi_vw )    ! j-mle streamfunction 
    316304      ENDIF 
    317305      ! 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/TRA/traqsr.F90

    r14537 r14607  
    293293      END_2D 
    294294      ! 
    295       ! TEMP: [tiling] This change not necessary and working array can use A2D(nn_hls) if using XIOS (subdomain support) 
    296       IF( .NOT. l_istiled .OR. ntile == nijtile )  THEN                ! Do only for the full domain 
    297          IF( iom_use('qsr3d') ) THEN      ! output the shortwave Radiation distribution 
    298             ALLOCATE( zetot(jpi,jpj,jpk) ) 
    299             zetot(:,:,nksr+1:jpk) = 0._wp     ! below ~400m set to zero 
    300             DO jk = nksr, 1, -1 
    301                zetot(:,:,jk) = zetot(:,:,jk+1) + qsr_hc(:,:,jk) * rho0_rcp 
    302             END DO 
    303             CALL iom_put( 'qsr3d', zetot )   ! 3D distribution of shortwave Radiation 
    304             DEALLOCATE( zetot ) 
    305          ENDIF 
     295      IF( iom_use('qsr3d') ) THEN      ! output the shortwave Radiation distribution 
     296         ALLOCATE( zetot(A2D(nn_hls),jpk) ) 
     297         zetot(:,:,nksr+1:jpk) = 0._wp     ! below ~400m set to zero 
     298         DO_3DS(0, 0, 0, 0, nksr, 1, -1) 
     299            zetot(ji,jj,jk) = zetot(ji,jj,jk+1) + qsr_hc(ji,jj,jk) * rho0_rcp 
     300         END_3D 
     301         CALL iom_put( 'qsr3d', zetot )   ! 3D distribution of shortwave Radiation 
     302         DEALLOCATE( zetot ) 
    306303      ENDIF 
    307304      ! 
  • NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/OCE/TRA/trasbc.F90

    r14537 r14607  
    142142            sbc_tsc(ji,jj,jp_sal) = sbc_tsc(ji,jj,jp_sal) + r1_rho0 * emp(ji,jj) * pts(ji,jj,1,jp_sal,Kmm) 
    143143         END_2D                                 !==>> output c./d. term 
    144          IF( .NOT. l_istiled .OR. ntile == nijtile )  THEN             ! Do only on the last tile 
    145             IF( iom_use('emp_x_sst') )   CALL iom_put( "emp_x_sst", emp (:,:) * pts(:,:,1,jp_tem,Kmm) ) 
    146             IF( iom_use('emp_x_sss') )   CALL iom_put( "emp_x_sss", emp (:,:) * pts(:,:,1,jp_sal,Kmm) ) 
    147          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) ) 
    148146      ENDIF 
    149147      ! 
     
    181179      ENDIF 
    182180 
    183       IF( .NOT. l_istiled .OR. ntile == nijtile )  THEN                ! Do only on the last tile 
    184           IF( iom_use('rnf_x_sst') )   CALL iom_put( "rnf_x_sst", rnf*pts(:,:,1,jp_tem,Kmm) )   ! runoff term on sst 
    185           IF( iom_use('rnf_x_sss') )   CALL iom_put( "rnf_x_sss", rnf*pts(:,:,1,jp_sal,Kmm) )   ! runoff term on sss 
    186       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 
    187183 
    188184#if defined key_asminc 
Note: See TracChangeset for help on using the changeset viewer.