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/rrtm/readaerosolstrato1_rrtm.F90

    r2744 r3413  
    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    USE xios
    2121
    2222    IMPLICIT NONE
     
    4545    REAL, ALLOCATABLE:: tauaerstrat_mois(:, :, :)
    4646    REAL, ALLOCATABLE:: tauaerstrat_mois_glo(:, :)
     47    REAL, ALLOCATABLE:: tauaerstrat_mpi(:, :)
    4748
    4849! For NetCDF:
     
    102103    n_lat = size(latitude)
    103104    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 
     105
     106    IF (grid_type/=unstructured) THEN
     107      IF (n_lat.NE.nbp_lat) THEN
     108         print *,'Le nombre de lat n est pas egal a nbp_lat'
     109         STOP
     110      ENDIF
     111    ENDIF
     112   
    109113    CALL nf95_inq_varid(ncid_in, "LON", varid)
    110114    CALL nf95_gw_var(ncid_in, varid, longitude)
    111115    n_lon = size(longitude)
    112116    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 
     117
     118    IF (grid_type/=unstructured) THEN
     119      IF (n_lon.NE.nbp_lon) THEN
     120         print *,'Le nombre de lon n est pas egal a nbp_lon'
     121         STOP
     122      ENDIF
     123    ENDIF
     124   
     125   
    118126    CALL nf95_inq_varid(ncid_in, "TIME", varid)
    119127    CALL nf95_gw_var(ncid_in, varid, time)
     
    144152!---reduce to a klon_glo grid
    145153    CALL grid2dTo1d_glo(tauaerstrat_mois,tauaerstrat_mois_glo)
    146 
     154   
     155    ELSE
     156      ALLOCATE(tauaerstrat_mois(0,0,0))
    147157    ENDIF !--is_mpi_root and is_omp_root
    148158
     
    153163
    154164!--scatter on all proc
    155     CALL scatter(tauaerstrat_mois_glo,tau_aer_strat)
    156 
     165   
     166    IF (grid_type==unstructured) THEN
     167      IF (is_omp_master) THEN
     168        ALLOCATE(tauaerstrat_mpi(klon_mpi,klev))
     169        CALL xios_send_field("taustrat_in",tauaerstrat_mois)
     170        CALL xios_recv_field("taustrat_out",tauaerstrat_mpi)
     171      ELSE
     172        ALLOCATE(tauaerstrat_mpi(0,0))
     173      ENDIF
     174      CALL scatter_omp(tauaerstrat_mpi,tau_aer_strat)
     175    ELSE 
     176      CALL scatter(tauaerstrat_mois_glo,tau_aer_strat)
     177    ENDIF
     178   
    157179    IF (is_mpi_root.AND.is_omp_root) THEN
    158180!
Note: See TracChangeset for help on using the changeset viewer.