Ignore:
Timestamp:
Jun 12, 2023, 4:38:28 PM (21 months ago)
Author:
romain.vande
Message:

Mars PEM :

Adapt PEM to 1d runs.
Cleaning of names and unused variables.
Correct minor errors.
Adapt and correct reshape_xios_output utilitary for 1d diagfi output.

RV

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/evolution/read_data_GCM.F90

    r2963 r2980  
    1 !
    2 ! $Id $
    3 !
    41SUBROUTINE read_data_GCM(fichnom,timelen, iim_input,jjm_input,ngrid,nslope,vmr_co2_gcm_phys,ps_timeseries, &
    52             min_co2_ice,min_h2o_ice,tsurf_ave,tsoil_ave,tsurf_gcm,tsoil_gcm,q_co2,q_h2o,co2_ice_slope, &
     
    2825  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
    2926  INTEGER, INTENT(IN) :: timelen                   ! number of times stored in the file
    30   INTEGER :: iim_input,jjm_input,ngrid,nslope            ! number of points in the lat x lon dynamical grid, number of subgrid slopes
     27  INTEGER :: iim_input,jjm_input,ngrid,nslope      ! number of points in the lat x lon dynamical grid, number of subgrid slopes
    3128! Ouputs
    3229  REAL, INTENT(OUT) ::  min_co2_ice(ngrid,nslope) ! Minimum of co2 ice  per slope of the year [kg/m^2]
     
    105102     print *, "Downloading data for surface pressure done"
    106103     print *, "nslope=", nslope
     104
     105if(nslope.gt.1) then
     106
    107107     print *, "Downloading data for co2ice_slope ..."
    108 
    109 if(nslope.gt.1) then
    110108
    111109DO islope=1,nslope
     
    178176    call get_var3("tsurf", tsurf_gcm_dyn(:,:,1,:))
    179177#ifndef CPP_STD
    180     call get_var3("watercap", watercap_slope(:,:,1,:))
     178!    call get_var3("watercap", watercap_slope(:,:,1,:))
     179  watercap_slope(:,:,1,:)=1.
    181180#endif
    182181
     
    198197    tsurf_ave_dyn(:,:,:)=SUM(tsurf_gcm_dyn(:,:,:,:),4)/timelen
    199198
     199#ifndef CPP_1D
    200200  DO islope = 1,nslope
    201201    DO t=1,timelen
     
    203203    ENDDO
    204204  ENDDO
     205#endif
    205206
    206207  if(soil_pem) then
     
    213214! By definition, a density is positive, we get rid of the negative values
    214215  DO i=1,iim+1
    215     DO j = 1, jjm+1
     216    DO j = 1, jjm_input+1
    216217       DO islope=1,nslope
    217218          if (min_co2_ice_dyn(i,j,islope).LT.0) then
     
    226227
    227228  DO i=1,iim+1
    228     DO j = 1, jjm+1
     229    DO j = 1, jjm_input+1
    229230      DO t = 1, timelen
    230231         if (q_co2_dyn(i,j,t).LT.0) then
     
    243244    ENDDO
    244245  ENDDO
     246
     247#ifndef CPP_1D
    245248
    246249     CALL gr_dyn_fi(timelen,iim_input+1,jjm_input+1,ngrid,vmr_co2_gcm,vmr_co2_gcm_phys)
     
    269272     CALL gr_dyn_fi(nslope,iim_input+1,jjm_input+1,ngrid,tsurf_ave_dyn,tsurf_ave)
    270273
     274#else
     275
     276  vmr_co2_gcm_phys(1,:)=vmr_co2_gcm(1,1,:)
     277  ps_timeseries(1,:)=ps_GCM(1,1,:)
     278  q_co2(1,:)=q_co2_dyn(1,1,:)
     279  q_h2o(1,:)=q_h2o_dyn(1,1,:)
     280  min_co2_ice(1,:)=min_co2_ice_dyn(1,1,:)
     281  min_h2o_ice(1,:)=min_h2o_ice_dyn(1,1,:)
     282  if(soil_pem) then
     283    tsoil_ave(1,:,:)=tsoil_ave_dyn(1,1,:,:)
     284    tsoil_gcm(1,:,:,:)=tsoil_gcm_dyn(1,1,:,:,:)
     285    watersoil_density(1,:,:,:)=watersoil_density_dyn(1,1,:,:,:)
     286  endif !soil_pem
     287  tsurf_GCM(1,:,:)=tsurf_GCM_dyn(1,1,:,:)
     288  co2_ice_slope(1,:,:)=co2_ice_slope_dyn(1,1,:,:)
     289  tsurf_ave(1,:)=tsurf_ave_dyn(1,1,:)
     290
     291#endif
     292
    271293  CONTAINS
    272294
Note: See TracChangeset for help on using the changeset viewer.