Ignore:
Timestamp:
2021-07-30T18:36:29+02:00 (3 years ago)
Author:
agnes.ducharne
Message:

Integrated r5705 (solay now in meters in output files), and small changes with no impact on code (r6220, r6565, r6567) from the trunk. Checked with a 5d run.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_parallel/xios_orchidee.f90

    r7255 r7265  
    126126  SUBROUTINE xios_orchidee_init(MPI_COMM_ORCH,                   & 
    127127       date0,    year,      month,             day, julian_diff, & 
    128        lon_mpi,  lat_mpi,   soilth_lev ) 
     128       lon_mpi,  lat_mpi ) 
    129129 
    130130    USE grid, ONLY : grid_type, unstructured, regular_lonlat, regular_xy, nvertex, & 
    131131                     longitude, latitude, bounds_lon, bounds_lat, ind_cell_glo 
     132 
     133    USE vertical_soil_var, ONLY : znt, znh 
     134 
    132135    IMPLICIT NONE 
    133136    ! 
     
    141144    REAL(r_std), INTENT(in)                               :: julian_diff      !! Current day in the year [1,365(366)] 
    142145    REAL(r_std),DIMENSION (iim_g,jj_nb), INTENT(in)       :: lon_mpi, lat_mpi !! Longitudes and latitudes on MPI local domain 2D domain 
    143     REAL(r_std),DIMENSION (ngrnd), INTENT(in)             :: soilth_lev       !! Vertical soil levels for thermal scheme (m) 
    144146    ! 
    145147    !! 0.2 Local variables 
     
    357359       CALL xios_set_axis_attr("nparts",n_glo=nparts,VALUE=(/(REAL(i,r_std),i=1,nparts)/)) 
    358360       CALL xios_set_axis_attr("nlaip1", n_glo=nlai+1,VALUE=(/(REAL(i,r_std),i=1,nlai+1)/)) 
    359        CALL xios_set_axis_attr("ngrnd",n_glo=ngrnd ,VALUE=soilth_lev(:)) 
     361       CALL xios_set_axis_attr("ngrnd",n_glo=ngrnd ,VALUE=znt(:)) 
    360362       CALL xios_set_axis_attr("nstm", n_glo=nstm,VALUE=(/(REAL(i,r_std),i=1,nstm)/)) 
    361363       CALL xios_set_axis_attr("ncsm", n_glo=nscm,VALUE=(/(REAL(i,r_std),i=1,nscm)/)) 
    362364       CALL xios_set_axis_attr("nnobio", n_glo=nnobio,VALUE=(/(REAL(i,r_std),i=1,nnobio)/)) 
    363365       CALL xios_set_axis_attr("albtyp", n_glo=2,VALUE=(/(REAL(i,r_std),i=1,2)/)) 
    364        CALL xios_set_axis_attr("nslm", n_glo=nslm,VALUE=(/(REAL(i,r_std),i=1,nslm)/)) 
     366       CALL xios_set_axis_attr("nslm", n_glo=nslm,VALUE=znh(:)) 
    365367       CALL xios_set_axis_attr("P10", n_glo=10,VALUE=(/(REAL(i,r_std), i=1,10)/)) 
    366368       CALL xios_set_axis_attr("P100", n_glo=100,VALUE=(/(REAL(i,r_std), i=1,100)/)) 
Note: See TracChangeset for help on using the changeset viewer.