Ignore:
Timestamp:
Jun 22, 2016, 2:02:46 PM (9 years ago)
Author:
ymipsl
Message:

forgotten Update for Orchidee configuration.

YM

Location:
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/geometry_mod.f90

    r3900 r3942  
    5656    ALLOCATE(cell_area(klon))
    5757    ALLOCATE(ind_cell_glo(klon))
    58     IF (PRESENT(dx_)) ALLOCATE(dx(klon))
    59     IF (PRESENT(dy_))ALLOCATE(dy(klon))
     58    ALLOCATE(dx(klon))
     59    ALLOCATE(dy(klon))
    6060   
    6161    longitude(:) = longitude_(:)
     
    6767    cell_area(:) = cell_area_(:)
    6868    ind_cell_glo(:) = ind_cell_glo_(:)
     69    dx(:)=0
     70    dy(:)=0
    6971    IF (PRESENT(dx_)) dx(:) = dx_(:)
    7072    IF (PRESENT(dy_)) dy(:) = dy_(:)
  • dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/surf_land_orchidee_mod.F90

    r3831 r3942  
    1616  USE cpl_mod,      ONLY : cpl_send_land_fields
    1717  USE surface_data, ONLY : type_ocean
    18   USE geometry_mod, ONLY : dx, dy
     18  USE geometry_mod, ONLY : dx, dy, lon_degrees, lat_degrees, boundslon, boundslat,longitude, latitude, cell_area,  ind_cell_glo
    1919  USE mod_grid_phy_lmdz
    2020  USE mod_phys_lmdz_para
     21  USE nrtype, ONLY : PI
    2122
    2223  IMPLICIT NONE
     
    4748    USE print_control_mod, ONLY: lunout
    4849    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
    49 
     50    USE time_phylmdz_mod, ONLY : itau_phy
    5051!   
    5152! Cette routine sert d'interface entre le modele atmospherique et le
     
    151152    REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: lalo
    152153    !$OMP THREADPRIVATE(lalo)
     154! boundaries of cells
     155    REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE   :: bounds_lalo
     156    !$OMP THREADPRIVATE(bounds_lalo)
    153157! pts voisins
    154158    INTEGER,ALLOCATABLE, DIMENSION(:,:), SAVE :: neighbours
     
    164168    !$OMP THREADPRIVATE(lon_scat,lat_scat)
    165169
     170    REAL, ALLOCATABLE, DIMENSION (:), SAVE  :: area 
     171    !$OMP THREADPRIVATE(area)
     172
    166173    LOGICAL, SAVE                             :: lrestart_read = .TRUE.
    167174    !$OMP THREADPRIVATE(lrestart_read)
     
    194201    REAL, ALLOCATABLE, DIMENSION(:), SAVE     :: riverflow
    195202    !$OMP THREADPRIVATE(riverflow)
     203
     204    INTEGER :: orch_mpi_rank
     205    INTEGER :: orch_mpi_size
    196206   
    197207    INTEGER :: orch_omp_rank
    198208    INTEGER :: orch_omp_size
     209
     210    REAL, ALLOCATABLE, DIMENSION(:)         :: longitude_glo
     211    REAL, ALLOCATABLE, DIMENSION(:)         :: latitude_glo
     212    REAL, ALLOCATABLE, DIMENSION(:,:)       :: boundslon_glo
     213    REAL, ALLOCATABLE, DIMENSION(:,:)       :: boundslat_glo
     214    INTEGER, ALLOCATABLE, DIMENSION(:)      :: ind_cell_glo_glo
     215    INTEGER, ALLOCATABLE, SAVE,DIMENSION(:) :: ind_cell
     216    !$OMP THREADPRIVATE(ind_cell)
     217    INTEGER :: begin, end
     218   
    199219!
    200220! Fin definition
     
    216236       IF ( .NOT. ALLOCATED(albedo_keep)) THEN
    217237!ym          ALLOCATE(albedo_keep(klon))
    218 !ym bizarre que non alloué en knon precedement
     238!ym bizarre que non allou en knon precedement
    219239          ALLOCATE(albedo_keep(knon))
    220240          ALLOCATE(zlev(knon))
     
    239259       jg(klon) = nbp_lat
    240260
    241        IF ((.NOT. ALLOCATED(lalo))) THEN
     261       IF ((.NOT. ALLOCATED(area))) THEN
     262          ALLOCATE(area(knon), stat = error)
     263          IF (error /= 0) THEN
     264             abort_message='Pb allocation area'
     265             CALL abort_physic(modname,abort_message,1)
     266          ENDIF
     267       ENDIF
     268       DO igrid = 1, knon
     269          area(igrid) = cell_area(knindex(igrid))
     270       ENDDO
     271       
     272       IF (grid_type==unstructured) THEN
     273
     274
     275         IF ((.NOT. ALLOCATED(lon_scat))) THEN
     276            ALLOCATE(lon_scat(nbp_lon,nbp_lat), stat = error)
     277            IF (error /= 0) THEN
     278               abort_message='Pb allocation lon_scat'
     279               CALL abort_physic(modname,abort_message,1)
     280            ENDIF
     281         ENDIF
     282 
     283         IF ((.NOT. ALLOCATED(lat_scat))) THEN
     284            ALLOCATE(lat_scat(nbp_lon,nbp_lat), stat = error)
     285            IF (error /= 0) THEN
     286               abort_message='Pb allocation lat_scat'
     287               CALL abort_physic(modname,abort_message,1)
     288            ENDIF
     289         ENDIF
     290         CALL Gather(rlon,rlon_g)
     291         CALL Gather(rlat,rlat_g)
     292
     293         IF (is_mpi_root) THEN
     294            index = 1
     295            DO jj = 2, nbp_lat-1
     296               DO ij = 1, nbp_lon
     297                  index = index + 1
     298                  lon_scat(ij,jj) = rlon_g(index)
     299                  lat_scat(ij,jj) = rlat_g(index)
     300               ENDDO
     301            ENDDO
     302            lon_scat(:,1) = lon_scat(:,2)
     303            lat_scat(:,1) = rlat_g(1)
     304            lon_scat(:,nbp_lat) = lon_scat(:,2)
     305            lat_scat(:,nbp_lat) = rlat_g(klon_glo)
     306         ENDIF
     307     
     308         CALL bcast(lon_scat)
     309         CALL bcast(lat_scat)
     310               
     311       ELSE IF (grid_type==regular_lonlat) THEN
     312          IF ((.NOT. ALLOCATED(lalo))) THEN
    242313          ALLOCATE(lalo(knon,2), stat = error)
    243314          IF (error /= 0) THEN
     
    245316             CALL abort_physic(modname,abort_message,1)
    246317          ENDIF
    247        ENDIF
    248        IF ((.NOT. ALLOCATED(lon_scat))) THEN
    249           ALLOCATE(lon_scat(nbp_lon,nbp_lat), stat = error)
     318         ENDIF
     319
     320          IF ((.NOT. ALLOCATED(bounds_lalo))) THEN
     321          ALLOCATE(bounds_lalo(knon,nvertex,2), stat = error)
    250322          IF (error /= 0) THEN
    251              abort_message='Pb allocation lon_scat'
     323             abort_message='Pb allocation lalo'
    252324             CALL abort_physic(modname,abort_message,1)
    253325          ENDIF
    254        ENDIF
    255        IF ((.NOT. ALLOCATED(lat_scat))) THEN
    256           ALLOCATE(lat_scat(nbp_lon,nbp_lat), stat = error)
    257           IF (error /= 0) THEN
    258              abort_message='Pb allocation lat_scat'
    259              CALL abort_physic(modname,abort_message,1)
    260           ENDIF
    261        ENDIF
    262        lon_scat = 0.
    263        lat_scat = 0.
    264        DO igrid = 1, knon
    265           index = knindex(igrid)
    266           lalo(igrid,2) = rlon(index)
    267           lalo(igrid,1) = rlat(index)
    268        ENDDO
    269 
     326         ENDIF
    270327       
    271        
    272        CALL Gather(rlon,rlon_g)
    273        CALL Gather(rlat,rlat_g)
    274 
    275        IF (is_mpi_root) THEN
    276           index = 1
    277           DO jj = 2, nbp_lat-1
    278              DO ij = 1, nbp_lon
    279                 index = index + 1
    280                 lon_scat(ij,jj) = rlon_g(index)
    281                 lat_scat(ij,jj) = rlat_g(index)
    282              ENDDO
    283           ENDDO
    284           lon_scat(:,1) = lon_scat(:,2)
    285           lat_scat(:,1) = rlat_g(1)
    286           lon_scat(:,nbp_lat) = lon_scat(:,2)
    287           lat_scat(:,nbp_lat) = rlat_g(klon_glo)
    288        ENDIF
    289    
    290        CALL bcast(lon_scat)
    291        CALL bcast(lat_scat)
     328         IF ((.NOT. ALLOCATED(lon_scat))) THEN
     329            ALLOCATE(lon_scat(nbp_lon,nbp_lat), stat = error)
     330            IF (error /= 0) THEN
     331               abort_message='Pb allocation lon_scat'
     332               CALL abort_physic(modname,abort_message,1)
     333            ENDIF
     334         ENDIF
     335         IF ((.NOT. ALLOCATED(lat_scat))) THEN
     336            ALLOCATE(lat_scat(nbp_lon,nbp_lat), stat = error)
     337            IF (error /= 0) THEN
     338               abort_message='Pb allocation lat_scat'
     339               CALL abort_physic(modname,abort_message,1)
     340            ENDIF
     341         ENDIF
     342         lon_scat = 0.
     343         lat_scat = 0.
     344         DO igrid = 1, knon
     345            index = knindex(igrid)
     346            lalo(igrid,2) = rlon(index)
     347            lalo(igrid,1) = rlat(index)
     348            bounds_lalo(igrid,:,2)=boundslon(index,:)*180./PI
     349            bounds_lalo(igrid,:,1)=boundslat(index,:)*180./PI
     350         ENDDO
     351       
     352         CALL Gather(rlon,rlon_g)
     353         CALL Gather(rlat,rlat_g)
     354
     355         IF (is_mpi_root) THEN
     356            index = 1
     357            DO jj = 2, nbp_lat-1
     358               DO ij = 1, nbp_lon
     359                  index = index + 1
     360                  lon_scat(ij,jj) = rlon_g(index)
     361                  lat_scat(ij,jj) = rlat_g(index)
     362               ENDDO
     363            ENDDO
     364            lon_scat(:,1) = lon_scat(:,2)
     365            lat_scat(:,1) = rlat_g(1)
     366            lon_scat(:,nbp_lat) = lon_scat(:,2)
     367            lat_scat(:,nbp_lat) = rlat_g(klon_glo)
     368         ENDIF
     369     
     370         CALL bcast(lon_scat)
     371         CALL bcast(lat_scat)
     372       ENDIF
    292373!
    293374! Allouer et initialiser le tableau des voisins et des fraction de continents
     
    315396
    316397
    317        CALL Init_neighbours(knon,neighbours,knindex,pctsrf(:,is_ter))
     398       IF (grid_type==regular_lonlat) CALL Init_neighbours(knon,neighbours,knindex,pctsrf(:,is_ter))
    318399
    319400!
     
    381462 
    382463    IF (debut) THEN
     464
    383465       CALL Init_orchidee_index(knon,knindex,offset,ktindex)
    384        CALL Get_orchidee_communicator(orch_comm,orch_omp_size,orch_omp_rank)
     466       CALL Get_orchidee_communicator(orch_comm,orch_mpi_size,orch_mpi_rank, orch_omp_size,orch_omp_rank)
     467
     468        IF (grid_type==unstructured) THEN
     469           begin=offset+1
     470           end=offset+ktindex(knon)
     471           IF (orch_mpi_rank==orch_mpi_size-1 .AND. orch_omp_rank==orch_omp_size-1) end=nbp_lon*nbp_lat
     472         
     473           ALLOCATE(lalo(end-begin+1,2))
     474           ALLOCATE(bounds_lalo(end-begin+1,nvertex,2))
     475           ALLOCATE(ind_cell(end-begin+1))
     476           
     477           ALLOCATE(longitude_glo(klon_glo))
     478           CALL gather(longitude,longitude_glo)
     479           CALL bcast(longitude_glo)
     480           lalo(:,2)=longitude_glo(begin:end)*180./PI
     481 
     482           ALLOCATE(latitude_glo(klon_glo))
     483           CALL gather(latitude,latitude_glo)
     484           CALL bcast(latitude_glo)
     485           lalo(:,1)=latitude_glo(begin:end)*180./PI
     486
     487           ALLOCATE(boundslon_glo(klon_glo,nvertex))
     488           CALL gather(boundslon,boundslon_glo)
     489           CALL bcast(boundslon_glo)
     490           bounds_lalo(:,:,2)=boundslon_glo(begin:end,:)*180./PI
     491 
     492           ALLOCATE(boundslat_glo(klon_glo,nvertex))
     493           CALL gather(boundslat,boundslat_glo)
     494           CALL bcast(boundslat_glo)
     495           bounds_lalo(:,:,1)=boundslat_glo(begin:end,:)*180./PI
     496         
     497           ALLOCATE(ind_cell_glo_glo(klon_glo))
     498           CALL gather(ind_cell_glo,ind_cell_glo_glo)
     499           CALL bcast(ind_cell_glo_glo)
     500           ind_cell(:)=ind_cell_glo_glo(begin:end)
     501         
     502         ENDIF
     503
    385504       CALL Init_synchro_omp
    386505       
    387506       IF (knon > 0) THEN
     507 
    388508#ifdef CPP_VEGET
    389509         CALL Init_intersurf(nbp_lon,nbp_lat,knon,ktindex,offset,orch_omp_size,orch_omp_rank,orch_comm)
     
    396516#ifdef CPP_VEGET
    397517          CALL intersurf_main (itime+itau_phy-1,nbp_lon,nbp_lat, knon, ktindex, dtime, &
    398                lrestart_read, lrestart_write, lalo, &
     518               lrestart_read, lrestart_write, grid_type, lalo, bounds_lalo, area, ind_cell, &
    399519               contfrac, neighbours, resolution, date0, &
    400                zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
    401                cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
    402                precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
    403                evap, fluxsens, fluxlat, coastalflow, riverflow, &
    404                tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
    405                lon_scat, lat_scat, q2m, t2m)
     520               zlev,  u1_lay(1:knon), v1_lay(1:knon), spechum(1:knon), temp_air(1:knon), epot_air(1:knon), ccanopy(1:knon), &
     521               cdrag(1:knon), petA_orc(1:knon), peqA_orc(1:knon), petB_orc(1:knon), peqB_orc(1:knon), &
     522               precip_rain(1:knon), precip_snow(1:knon), lwdown(1:knon), swnet(1:knon), swdown_vrai(1:knon), ps(1:knon), &
     523               evap(1:knon), fluxsens(1:knon), fluxlat(1:knon), coastalflow(1:knon), riverflow(1:knon), &
     524               tsol_rad(1:knon), tsurf_new(1:knon), qsurf(1:knon), albedo_out(1:knon,:), emis_new(1:knon), z0_new(1:knon), &
     525               lon_scat, lat_scat, q2m(1:knon), t2m(1:knon))
    406526#endif         
    407527       ENDIF
     
    420540#ifdef CPP_VEGET   
    421541       CALL intersurf_main (itime+itau_phy,nbp_lon,nbp_lat, knon, ktindex, dtime,  &
    422             lrestart_read, lrestart_write, lalo, &
     542            lrestart_read, lrestart_write, grid_type, lalo, bounds_lalo, area, ind_cell, &
    423543            contfrac, neighbours, resolution, date0, &
    424544            zlev,  u1_lay(1:knon), v1_lay(1:knon), spechum(1:knon), temp_air(1:knon), epot_air(1:knon), ccanopy(1:knon), &
     
    427547            evap(1:knon), fluxsens(1:knon), fluxlat(1:knon), coastalflow(1:knon), riverflow(1:knon), &
    428548            tsol_rad(1:knon), tsurf_new(1:knon), qsurf(1:knon), albedo_out(1:knon,:), emis_new(1:knon), z0_new(1:knon), &
    429             lon_scat, lat_scat, q2m, t2m)
     549            lon_scat, lat_scat, q2m(1:knon), t2m(1:knon))
    430550#endif       
    431551    ENDIF
     
    500620!
    501621
    502   SUBROUTINE Get_orchidee_communicator(orch_comm,orch_omp_size,orch_omp_rank)
     622  SUBROUTINE Get_orchidee_communicator(orch_comm, orch_mpi_size, orch_mpi_rank, orch_omp_size,orch_omp_rank)
    503623  USE  mod_surf_para
    504624     
     
    508628
    509629    INTEGER,INTENT(OUT) :: orch_comm
     630    INTEGER,INTENT(OUT) :: orch_mpi_size
     631    INTEGER,INTENT(OUT) :: orch_mpi_rank
    510632    INTEGER,INTENT(OUT) :: orch_omp_size
    511633    INTEGER,INTENT(OUT) :: orch_omp_rank
     
    527649#ifdef CPP_MPI   
    528650      CALL MPI_COMM_SPLIT(COMM_LMDZ_PHY,color,mpi_rank,orch_comm,ierr)
     651      CALL MPI_COMM_SIZE(orch_comm,orch_mpi_size,ierr)
     652      CALL MPI_COMM_RANK(orch_comm,orch_mpi_rank,ierr)
    529653#endif
    530654   
Note: See TracChangeset for help on using the changeset viewer.