Ignore:
Timestamp:
Nov 21, 2019, 4:43:45 PM (4 years ago)
Author:
lguez
Message:

Merge revisions 3427:3600 of trunk into branch Ocean_skin

Location:
LMDZ6/branches/Ocean_skin
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin

  • LMDZ6/branches/Ocean_skin/libf/phylmd/rrtm/readaerosolstrato1_rrtm.F90

    r2744 r3605  
    22! $Id: readaerosolstrato1_rrtm.F90 2526 2016-05-26 22:13:40Z oboucher $
    33!
     4
    45SUBROUTINE readaerosolstrato1_rrtm(debut)
    56
     
    910
    1011    USE phys_cal_mod, ONLY : mth_cur
    11     USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, grid2dTo1d_glo
    12     USE mod_phys_lmdz_mpi_data, ONLY :  is_mpi_root
    13     USE mod_phys_lmdz_omp_data, ONLY :  is_omp_root
     12    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, klon_glo, grid2dTo1d_glo, grid_type, unstructured
    1413    USE mod_phys_lmdz_para
    1514    USE phys_state_var_mod
     
    1918    USE YOERAD, ONLY : NLW
    2019    USE YOMCST
     20#ifdef CPP_XIOS
     21    USE xios
     22#endif
    2123
    2224    IMPLICIT NONE
     
    4547    REAL, ALLOCATABLE:: tauaerstrat_mois(:, :, :)
    4648    REAL, ALLOCATABLE:: tauaerstrat_mois_glo(:, :)
     49    REAL, ALLOCATABLE:: tauaerstrat_mpi(:, :)
    4750
    4851! For NetCDF:
     
    102105    n_lat = size(latitude)
    103106    print *, 'LAT aerosol strato=', n_lat, latitude
    104     IF (n_lat.NE.nbp_lat) THEN
    105        print *,'Le nombre de lat n est pas egal a nbp_lat'
    106        STOP
    107     ENDIF
    108 
     107
     108    IF (grid_type/=unstructured) THEN
     109      IF (n_lat.NE.nbp_lat) THEN
     110         print *,'Le nombre de lat n est pas egal a nbp_lat'
     111         STOP
     112      ENDIF
     113    ENDIF
     114   
    109115    CALL nf95_inq_varid(ncid_in, "LON", varid)
    110116    CALL nf95_gw_var(ncid_in, varid, longitude)
    111117    n_lon = size(longitude)
    112118    print *, 'LON aerosol strato=', n_lon, longitude
    113     IF (n_lon.NE.nbp_lon) THEN
    114        print *,'Le nombre de lon n est pas egal a nbp_lon'
    115        STOP
    116     ENDIF
    117 
     119
     120    IF (grid_type/=unstructured) THEN
     121      IF (n_lon.NE.nbp_lon) THEN
     122         print *,'Le nombre de lon n est pas egal a nbp_lon'
     123         STOP
     124      ENDIF
     125    ENDIF
     126   
     127   
    118128    CALL nf95_inq_varid(ncid_in, "TIME", varid)
    119129    CALL nf95_gw_var(ncid_in, varid, time)
     
    144154!---reduce to a klon_glo grid
    145155    CALL grid2dTo1d_glo(tauaerstrat_mois,tauaerstrat_mois_glo)
    146 
     156   
     157    ELSE
     158      ALLOCATE(tauaerstrat_mois(0,0,0))
    147159    ENDIF !--is_mpi_root and is_omp_root
    148160
     
    153165
    154166!--scatter on all proc
    155     CALL scatter(tauaerstrat_mois_glo,tau_aer_strat)
    156 
     167   
     168    IF (grid_type==unstructured) THEN
     169#ifdef CPP_XIOS
     170      IF (is_omp_master) THEN
     171        ALLOCATE(tauaerstrat_mpi(klon_mpi,klev))
     172        CALL xios_send_field("taustrat_in",tauaerstrat_mois)
     173        CALL xios_recv_field("taustrat_out",tauaerstrat_mpi)
     174      ELSE
     175        ALLOCATE(tauaerstrat_mpi(0,0))
     176      ENDIF
     177      CALL scatter_omp(tauaerstrat_mpi,tau_aer_strat)
     178#endif
     179    ELSE 
     180      CALL scatter(tauaerstrat_mois_glo,tau_aer_strat)
     181    ENDIF
     182   
    157183    IF (is_mpi_root.AND.is_omp_root) THEN
    158184!
Note: See TracChangeset for help on using the changeset viewer.