Ignore:
Timestamp:
Nov 12, 2018, 1:52:29 PM (6 years ago)
Author:
Laurent Fairhead
Message:

Inclusion of Yann's latest (summer/fall 2018) modifications for
convergence of DYNAMICO/LMDZ physics
YM/LF

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/regr_pr_time_av_m.F90

    r3411 r3413  
    106106  USE assert_m,       ONLY: assert
    107107  USE assert_eq_m,    ONLY: assert_eq
    108 !  USE comvert_mod,    ONLY: scaleheight
     108!!  USE comvert_mod,    ONLY: scaleheight
    109109  USE interpolation,  ONLY: locate
    110110  USE regr_conserv_m, ONLY: regr_conserv
    111111  USE regr_lint_m,    ONLY: regr_lint
    112112  USE slopes_m,       ONLY: slopes
    113   USE mod_phys_lmdz_mpi_data,       ONLY: is_mpi_root
    114   USE mod_grid_phy_lmdz,            ONLY: nbp_lon, nbp_lat, nbp_lev
    115   USE mod_phys_lmdz_transfert_para, ONLY: scatter2d, scatter
     113  USE mod_phys_lmdz_para,           ONLY: is_mpi_root,is_master
     114  USE mod_grid_phy_lmdz,            ONLY: nbp_lon, nbp_lat, nbp_lev, klon_glo, grid_type, unstructured
     115  USE mod_phys_lmdz_transfert_para, ONLY: scatter2d, scatter, gather
    116116  USE phys_cal_mod,                 ONLY: calend, year_len, days_elapsed, jH_cur
     117  USE geometry_mod,                 ONLY: ind_cell_glo
    117118!-------------------------------------------------------------------------------
    118119! Arguments:
     
    157158  REAL, DIMENSION(nbp_lon, nbp_lat)   :: ps1, pt1, ot1
    158159  REAL, DIMENSION(klon)               :: ps2, pt2, ot2, ptropou
     160  INTEGER,ALLOCATABLE :: ind_cell_glo_glo(:)
    159161  LOGICAL :: ll
    160162!-------------------------------------------------------------------------------
     
    230232    CALL bcast(lO3Trop); CALL bcast(linterp)
    231233  END IF
     234 
     235  IF (is_master) THEN
     236    ALLOCATE(ind_cell_glo_glo(klon_glo))
     237  ELSE
     238    ALLOCATE(ind_cell_glo_glo(0))
     239  ENDIF
     240  CALL gather(ind_cell_glo,ind_cell_glo_glo)
     241  IF (is_master .AND. grid_type==unstructured) v1(:,:,:,:)=v1(:,ind_cell_glo_glo(:),:,:)
     242 
    232243  CALL scatter2d(v1,v2)
     244
    233245  !--- No "ps" in input file => assumed to be equal to current LMDZ ground press
    234   IF(lPrSurf) THEN; CALL scatter2d(ps1,ps2); ELSE; ps2=pint_ou(:,1); END IF
    235   IF(lPrTrop) CALL scatter2d(pt1,pt2)
    236   IF(lO3Trop) CALL scatter2d(ot1,ot2)
    237 
     246  IF(lPrSurf) THEN
     247    IF (is_master .AND. grid_type==unstructured) ps1(:,:)=ps1(:,ind_cell_glo_glo(:))
     248    CALL scatter2d(ps1,ps2)
     249  ELSE
     250   ps2=pint_ou(:,1)
     251  END IF
     252
     253  IF(lPrTrop) THEN
     254    IF (is_master .AND. grid_type==unstructured) pt1(:,:)=pt1(:,ind_cell_glo_glo(:))
     255    CALL scatter2d(pt1,pt2)
     256  ENDIF
     257
     258  IF(lO3Trop) THEN
     259    IF (is_master .AND. grid_type==unstructured) ot1(:,:)=ot1(:,ind_cell_glo_glo(:))
     260    CALL scatter2d(ot1,ot2)
     261  ENDIF
    238262  !--- REGRID IN PRESSURE ; 3rd index inverted because "paprs" is decreasing
    239263  IF(.NOT.lAdjTro) THEN
Note: See TracChangeset for help on using the changeset viewer.