Ignore:
Timestamp:
11/02/20 11:46:25 (4 years ago)
Author:
ymipsl
Message:

Ensemble management for orchidee.

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • CONFIG_DEVT/LMDZOR_V6.2_work_ENSEMBLES/modeles/ORCHIDEE/src_parallel/xios_orchidee.f90

    r5477 r5493  
    130130    USE grid, ONLY : grid_type, unstructured, regular_lonlat, regular_xy, nvertex, & 
    131131                     longitude, latitude, bounds_lon, bounds_lat, ind_cell_glo 
     132    USE mod_orchidee_ensemble, ONLY : ensemble_management, whole_ensemble_size, whole_ensemble_rank, COMM_ORCHIDEE_ENSEMBLE 
    132133    IMPLICIT NONE 
    133134    ! 
     
    271272       !! 2. Context initialization 
    272273       ! 
    273        CALL xios_context_initialize("orchidee",MPI_COMM_ORCH) 
     274       CALL xios_context_initialize("orchidee",COMM_ORCHIDEE_ENSEMBLE) 
    274275       CALL xios_get_handle("orchidee",ctx_hdl_orchidee) 
    275276       CALL xios_set_current_context(ctx_hdl_orchidee) 
     
    352353       !! 4. Axis definition 
    353354       ! 
     355       CALL xios_set_axis_attr("ensemble",n_glo=whole_ensemble_size,begin=whole_ensemble_rank, n=1) 
     356  
    354357       CALL xios_set_axis_attr("nvm",n_glo=nvm ,VALUE=(/(REAL(i,r_std),i=1,nvm)/)) 
    355358       CALL xios_set_axis_attr("nlut",n_glo=nlut ,VALUE=(/(REAL(i,r_std),i=1,nlut)/)) 
Note: See TracChangeset for help on using the changeset viewer.