Changeset 7259


Ignore:
Timestamp:
2021-07-27T17:15:46+02:00 (3 years ago)
Author:
agnes.ducharne
Message:

As in r6385, so that interpolation using aggregate_p is now done in parallel. Runtime has been divided by 6 for a 5d run from scratch at 2deg offline!

Location:
branches/ORCHIDEE_2_2/ORCHIDEE
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_driver/orchideedriver.f90

    r7257 r7259  
    412412  ! Variables *_g were allocated with the CALL init_grid 
    413413  ! 
    414   IF ( is_root_prc) THEN 
    415      ! 
    416      lalo_g(:,:) = lalo_glo(:,:) 
    417      lon_g(:,:) = lon_glo(:,:) 
    418      lat_g(:,:) = lat_glo(:,:) 
    419      ! 
    420   ENDIF 
     414  ! 
     415  lalo_g(:,:) = lalo_glo(:,:) 
     416  contfrac_g(:) = contfrac_glo(:) 
     417  lon_g(:,:) = lon_glo(:,:) 
     418  lat_g(:,:) = lat_glo(:,:) 
    421419  ! 
    422420  ! 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_global/grid.f90

    r6289 r7259  
    443443    ! 
    444444    CALL grid_scatter() 
     445    ! 
     446    CALL bcast(neighbours_g) 
     447    CALL bcast(resolution_g) 
    445448    ! 
    446449    IF ( printlev >= 3 ) WRITE(numout,*) 'Leaving grid_stuff' 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_global/interpol_help.f90

    r7258 r7259  
    4242  SUBROUTINE aggregate_2d (nbpt, lalo, neighbours, resolution, contfrac, & 
    4343       &                iml, jml, lon_rel, lat_rel, mask, callsign, & 
    44        &                incmax, indinc, areaoverlap, ok) 
     44       &                incmax, indinc, areaoverlap, ok, opt_nbpt_start, opt_nbpt_end) 
    4545 
    4646    USE grid, ONLY : global 
     
    6161    CHARACTER(LEN=*), INTENT(in) :: callsign             ! Allows to specify which variable is beeing treated 
    6262    INTEGER(i_std), INTENT(in)   :: incmax              ! Maximum point of the fine grid we can store. 
     63    INTEGER(i_std), OPTIONAL, INTENT(in)    :: opt_nbpt_start            ! Input Start grid cell interpolation  
     64    INTEGER(i_std), OPTIONAL, INTENT(in)    :: opt_nbpt_end              ! Input End grid cell interpolation 
    6365    ! 
    6466    ! Output 
    6567    ! 
    66     INTEGER(i_std), INTENT(out)  :: indinc(nbpt,incmax,2) 
    67     REAL(r_std), INTENT(out)      :: areaoverlap(nbpt,incmax) 
     68    INTEGER(i_std), INTENT(out)  :: indinc(:,:,:) 
     69    REAL(r_std), INTENT(out)      :: areaoverlap(:,:) 
    6870    LOGICAL, OPTIONAL, INTENT(out)      :: ok            ! return code 
    6971    ! 
     
    7880    REAL(r_std) :: domain_minlon,domain_maxlon,domain_minlat,domain_maxlat 
    7981    INTEGER(i_std) :: minLon(1), maxLon(1) 
     82    INTEGER(i_std) :: nbpt_start            ! Start grid cell interpolation  
     83    INTEGER(i_std) :: nbpt_end              ! End grid cell interpolation 
     84    INTEGER(i_std) :: landpoint_idx  
    8085 
    8186    INTEGER                  :: ALLOC_ERR 
     
    108113    ALLOCATE (searchind(iml*jml,2), STAT=ALLOC_ERR) 
    109114    IF (ALLOC_ERR/=0) CALL ipslerr_p(3,'aggregate_2d', 'ERROR IN ALLOCATION of searchind','','') 
     115 
     116    nbpt_start = 1 
     117    nbpt_end = nbpt 
     118    IF (PRESENT(opt_nbpt_start) .AND. PRESENT(opt_nbpt_end)) THEN 
     119        nbpt_start = opt_nbpt_start 
     120        nbpt_end = opt_nbpt_end 
     121    ENDIF 
    110122 
    111123    IF (PRESENT(ok)) ok = .TRUE. 
     
    256268    ! 
    257269    fopt_max = -1 
    258     DO ib =1, nbpt 
     270    DO ib = nbpt_start, nbpt_end 
     271       landpoint_idx = ib - nbpt_start + 1  
    259272       ! 
    260273       !   Give a progress meter 
     
    355368                   ay = (MIN(lat_up, laup_rel(ip,jp))-MAX(lat_low,lalow_rel(ip,jp)))*pi/180. * R_Earth 
    356369                   ! 
    357                    areaoverlap(ib, fopt) = ax*ay 
    358                    indinc(ib, fopt, 1) = ip 
    359                    indinc(ib, fopt, 2) = jp 
     370                   areaoverlap(landpoint_idx, fopt) = ax*ay 
     371                   indinc(landpoint_idx, fopt, 1) = ip 
     372                   indinc(landpoint_idx, fopt, 2) = jp 
    360373                   ! 
    361374                   ! If this point was 100% within the grid then we can de-select it from our 
     
    403416    ENDDO 
    404417    ! 
    405     DO ib=1,nbpt 
     418    DO ib=nbpt_start, nbpt_end 
     419       landpoint_idx = ib - nbpt_start + 1 
    406420       DO fopt=1,incmax 
    407           IF (( indinc(ib,fopt,1) == 0 .AND. indinc(ib,fopt,2) > 0) .OR.& 
    408                & ( indinc(ib,fopt,2) == 0 .AND. indinc(ib,fopt,1) > 0) ) THEN 
     421          IF (( indinc(landpoint_idx,fopt,1) == 0 .AND. indinc(landpoint_idx,fopt,2) > 0) .OR.& 
     422               & ( indinc(landpoint_idx,fopt,2) == 0 .AND. indinc(landpoint_idx,fopt,1) > 0) ) THEN 
    409423             WRITE(*,*) "aggregate_2d PROBLEM : point =",ib, fopt," Indicies = ", & 
    410                   & indinc(ib,fopt,1), indinc(ib,fopt,2), areaoverlap(ib,fopt) 
     424                  & indinc(landpoint_idx,fopt,1), indinc(landpoint_idx,fopt,2), areaoverlap(landpoint_idx,fopt) 
    411425          ENDIF 
    412426       ENDDO 
     
    815829    REAL(r_std), INTENT(out)       :: sub_area(nbpt,nbvmax)  
    816830    LOGICAL, OPTIONAL, INTENT(out) :: ok            ! return code 
    817  
    818     INTEGER(i_std)   :: sub_index_g(nbp_glo,nbvmax,2) 
    819     REAL(r_std)       :: sub_area_g(nbp_glo,nbvmax) 
     831    INTEGER(i_std)                 :: nbp_start, nbp_end 
     832 
     833 
     834    INTEGER(i_std), ALLOCATABLE, DIMENSION(:,:,:)  :: sub_index_g  
     835    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)       :: sub_area_g  
    820836 
    821837    IF ( grid_type == regular_lonlat ) THEN 
    822        IF (is_root_prc) CALL aggregate_2d(nbp_glo, lalo_g, neighbours_g, resolution_g, contfrac_g, & 
    823             &                                  iml, jml, lon_ful, lat_ful, mask, callsign,   & 
    824             &                                  nbvmax, sub_index_g, sub_area_g, ok) 
     838       nbp_start = nbp_mpi_para_begin(mpi_rank) + (nbp_omp_para_begin(omp_rank) - 1) 
     839#ifdef CPP_OMP 
     840       ! possible abstraction?  
     841       nbp_end = nbp_mpi_para_begin(mpi_rank) + (nbp_omp_para_end(omp_rank) - 1)  
     842#else 
     843       nbp_end = nbp_mpi_para_end(mpi_rank) 
     844#endif 
     845       CALL aggregate_2d(nbp_glo, lalo_g, neighbours_g, resolution_g, contfrac_g, & 
     846            &             iml, jml, lon_ful, lat_ful, mask, callsign,   & 
     847            &             nbvmax, sub_index, sub_area, ok, & 
     848                          nbp_start, nbp_end) 
    825849    ELSE IF ( grid_type == regular_xy ) THEN 
     850        ALLOCATE(sub_index_g(nbp_glo, nbvmax, 2)) 
     851        ALLOCATE(sub_area_g(nbp_glo, nbvmax)) 
     852 
    826853       IF ( proj_stack(1)%code > undef_int-1 ) THEN 
    827854          CALL ipslerr(3, "aggregate_2d_p", "Regular_xy projection was not intialized.", & 
     
    831858            &                               iml, jml, lon_ful, lat_ful, mask, callsign,   & 
    832859            &                               nbvmax, sub_index_g, sub_area_g, ok) 
     860 
     861       CALL BCAST(ok) 
     862       CALL scatter(sub_index_g,sub_index) 
     863       CALL scatter(sub_area_g,sub_area) 
     864 
     865       DEALLOCATE(sub_index_g) 
     866       DEALLOCATE(sub_area_g) 
    833867    ELSE 
    834868       CALL ipslerr(3, "aggregate_2d_p", "Interpolation is only possible for regular lat/lon grids for the moment.", & 
     
    836870    ENDIF 
    837871    ! 
    838     CALL BCAST(ok) 
    839     CALL scatter(sub_index_g,sub_index) 
    840     CALL scatter(sub_area_g,sub_area) 
    841872    
    842873  END SUBROUTINE aggregate_2d_p 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/intersurf.f90

    r6370 r7259  
    242242    CALL gather2D_mpi(lon,lon_g) 
    243243    CALL gather2D_mpi(lat,lat_g) 
     244 
     245    CALL bcast(lalo_g) 
     246    CALL bcast(contfrac_g) 
    244247     
    245248    CALL ioipslctrl_restini(kjit, date0, xrdt, rest_id, rest_id_stom, itau_offset, date0_shifted) 
     
    955958    lalo(:,:) = latlon(:,:) 
    956959    CALL gather(lalo,lalo_g) 
     960    CALL bcast(lalo_g) 
    957961    ! 
    958962    !- 
     
    962966    neighbours(:,:) = zneighbours(:,:) 
    963967    CALL gather(neighbours,neighbours_g) 
     968    CALL bcast(neighbours_g) 
    964969    ! 
    965970    resolution(:,:) = zresolution(:,:) 
    966971    CALL gather(resolution,resolution_g) 
     972    CALL bcast(resolution_g) 
    967973    ! 
    968974    IF (grid_type==regular_lonlat) area(:) = resolution(:,1)*resolution(:,2) 
    969975    CALL gather(area,area_g) 
     976    CALL bcast(area_g) 
    970977    ! 
    971978    !- Store the fraction of the continents only once so that the user 
     
    974981    contfrac(:) = zcontfrac(:) 
    975982    CALL gather(contfrac,contfrac_g) 
     983    CALL bcast(contfrac_g) 
    976984    ! 
    977985    ! 
Note: See TracChangeset for help on using the changeset viewer.