Changeset 2937


Ignore:
Timestamp:
Apr 13, 2023, 11:04:49 AM (20 months ago)
Author:
llange
Message:

PEM
Thermal Inertia is now only read in the start and not read in the xios
file
Fixing few bug (problem of allocation and index for update_soil and some
variables in the pem)
LL

Location:
trunk/LMDZ.COMMON/libf/evolution
Files:
5 edited

Legend:

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

    r2888 r2937  
    8080    print *, "Tendencies on ice increasing=", pos_tend
    8181    print *, "This can be due to the absence of water ice in the PCM run!!"
    82       call criterion_waterice_stop(cell_area,1.,qsurf(:,:)*0.,STOPPING,ngrid,cell_area)
     82    print *,cell_area,qsurf(:,:),ngrid,STOPPING
     83      call criterion_waterice_stop(cell_area,1.,qsurf(:,:)*0.,STOPPING,ngrid,qsurf(:,:)*0.)
    8384      do i=1,ngrid
    8485         do islope=1,nslope
  • trunk/LMDZ.COMMON/libf/evolution/pem.F90

    r2919 r2937  
    195195!!!!!!!!!!!!!!!!!!!!!!!! SLOPE
    196196      REAL ,allocatable :: watercap_slope(:,:)                           ! Physics x Nslope: watercap per slope
    197       REAL ,allocatable :: watercap_slope_saved                          ! Value saved at the previous time step
     197      REAL ::              watercap_slope_saved                          ! Value saved at the previous time step
    198198      REAL , dimension(:,:), allocatable :: min_co2_ice_1                ! ngrid field : minimum of co2 ice at each point for the first year [kg/m^2]
    199199      REAL , dimension(:,:), allocatable :: min_co2_ice_2                ! ngrid field : minimum of co2 ice at each point for the second year [kg/m^2]
     
    223223     REAL, ALLOCATABLE :: inertiesoil(:,:)    !Physic x Depth  Thermal inertia of the mesh for restart [SI]
    224224
    225      REAL, ALLOCATABLE :: TI_GCM(:,:,:)       ! Physic x Depth x Slope Averaged GCM Thermal Inertia per slope  [SI]
    226      REAL, ALLOCATABLE :: TI_GCM_start(:,:,:) ! Same but for the start
     225     REAL, ALLOCATABLE :: TI_GCM(:,:,:) ! Same but for the start
    227226
    228227     REAL,ALLOCATABLE  :: ice_depth(:,:)      ! Physic x SLope: Ice table depth [m]
     
    369368
    370369      allocate(watercap_slope(ngrid,nslope))
    371       allocate(TI_GCM_start(ngrid,nsoilmx,nslope))
     370      allocate(TI_GCM(ngrid,nsoilmx,nslope))
    372371      allocate(inertiesoil(ngrid,nsoilmx))
    373372
     
    380379              watercap,inertiesoil,nslope,tsurf_slope,           &
    381380              tsoil_slope,co2ice_slope,def_slope,def_slope_mean, &
    382               subslope_dist,major_slope,albedo_slope,emiss_slope, TI_GCM_start,     &
     381              subslope_dist,major_slope,albedo_slope,emiss_slope, TI_GCM,     &
    383382              qsurf_slope,watercap_slope)
    384383
    385      if(soil_pem) then
    386        deallocate(TI_GCM_start) !not used then
    387      endif
     384
    388385
    389386! Remove unphysical values of surface tracer
     
    496493     allocate(tsurf_GCM_timeseries(ngrid,nslope,timelen))
    497494     allocate(tsoil_GCM_timeseries(ngrid,nsoilmx,nslope,timelen))
    498      allocate(TI_GCM(ngrid,nsoilmx,nslope))
    499495     allocate(q_co2_PEM_phys(ngrid,timelen))
    500496     allocate(q_h2o_PEM_phys(ngrid,timelen))
    501497     allocate(co2_ice_GCM_slope(ngrid,nslope,timelen))
    502498     allocate(watersurf_density_ave(ngrid,nslope))
    503      allocate(watersoil_density_timeseries(nslope,nsoilmx,nslope,timelen))
     499     allocate(watersoil_density_timeseries(ngrid,nsoilmx,nslope,timelen))
    504500
    505501     allocate(tsoil_ave_PEM_yr1(ngrid,nsoilmx_PEM,nslope))
     
    515511
    516512     call read_data_GCM("data_GCM_Y1.nc",timelen, iim,jjm,ngrid,nslope,vmr_co2_gcm,ps_timeseries,min_co2_ice_1,min_h2o_ice_1,&   
    517                        tsurf_ave_yr1,tsoil_ave_yr1, tsurf_GCM_timeseries,tsoil_GCM_timeseries,TI_GCM,q_co2_PEM_phys,q_h2o_PEM_phys,co2_ice_GCM_slope, &     
     513                       tsurf_ave_yr1,tsoil_ave_yr1, tsurf_GCM_timeseries,tsoil_GCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys,co2_ice_GCM_slope, &     
    518514                       watersurf_density_ave,watersoil_density_timeseries)
    519515
     
    524520
    525521     call read_data_GCM("data_GCM_Y2.nc",timelen,iim,jjm,ngrid,nslope,vmr_co2_gcm,ps_timeseries,min_co2_ice_2,min_h2o_ice_2, &
    526                   tsurf_ave,tsoil_ave, tsurf_GCM_timeseries,tsoil_GCM_timeseries,TI_GCM,q_co2_PEM_phys,q_h2o_PEM_phys,co2_ice_GCM_slope, &     
     522                  tsurf_ave,tsoil_ave, tsurf_GCM_timeseries,tsoil_GCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys,co2_ice_GCM_slope, &     
    527523                  watersurf_density_ave,watersoil_density_timeseries)
    528524
     
    835831! II.b. Evolution of the ice
    836832      print *, "Evolution of h2o ice"
     833     
    837834     call evol_h2o_ice_s_slope(qsurf_slope(:,igcm_h2o_ice,:),tendencies_h2o_ice,iim,jjm,ngrid,cell_area,STOPPING_1_water,nslope)
    838 
     835     
    839836     DO islope=1, nslope
    840837       write(str2(1:2),'(i2.2)') islope
     
    994991     call computeice_table_equilibrium(ngrid,nslope,nsoilmx_PEM,watercaptag,watersurf_density_ave,watersoil_density_PEM_ave,ice_depth)
    995992       
    996       print *, "Update soil propreties"
     993     print *, "Update soil propreties"
     994
    997995! II_d.4 Update the soil thermal properties
    998       call update_soil(ngrid,nslope,nsoilmx,nsoilmx_PEM,tendencies_h2o_ice,qsurf_slope(:,igcm_h2o_ice,:),global_ave_press_new, &
     996      call update_soil(ngrid,nslope,nsoilmx_PEM,tendencies_h2o_ice,qsurf_slope(:,igcm_h2o_ice,:),global_ave_press_new, &
    999997        ice_depth,TI_PEM)
    1000998
     
    11651163     fluxgeo_slope(:,:) = fluxgeo
    11661164     call interpolate_TIPEM_TIGCM(ngrid,nslope,nsoilmx_PEM,nsoilmx,TI_PEM,TI_GCM)
    1167      tsoil_slope(:,:,:) = tsoil_phys_PEM_timeseries(:,:,:,timelen)
    1168    else
    1169       TI_GCM(:,:,:)=TI_GCM_start(:,:,:)
     1165     tsoil_slope(:,:,:) = tsoil_phys_PEM_timeseries(:,:,:,timelen)     
    11701166   endif !soil_pem
    11711167
  • trunk/LMDZ.COMMON/libf/evolution/pemetat0.F90

    r2905 r2937  
    9090
    9191write(*,*)'Is start PEM?',startpem_file
    92 
     92startpem_file = .true.
    9393
    9494!1. Run
     
    287287  DO islope=1,nslope
    288288   write(num,fmt='(i2.2)') islope
    289    call get_field("mco2_reg_ads_slope"//num,m_co2_regolith_phys(:,:,islope),found)
     289   call get_field("mh2o_reg_ads_slope"//num,m_co2_regolith_phys(:,:,islope),found2)
    290290    if((.not.found2)) then
    291291       m_h2o_regolith_phys(:,:,:) = 0.
  • trunk/LMDZ.COMMON/libf/evolution/read_data_GCM.F90

    r2897 r2937  
    33!
    44SUBROUTINE read_data_GCM(fichnom,timelen, iim_input,jjm_input,ngrid,nslope,vmr_co2_gcm_phys,ps_timeseries, &
    5              min_co2_ice,min_h2o_ice,tsurf_ave,tsoil_ave,tsurf_gcm,tsoil_gcm,TI_ave,q_co2,q_h2o,co2_ice_slope, &
     5             min_co2_ice,min_h2o_ice,tsurf_ave,tsoil_ave,tsurf_gcm,tsoil_gcm,q_co2,q_h2o,co2_ice_slope, &
    66             watersurf_density_ave,watersoil_density)
    77
     
    4444  REAL , INTENT(OUT) ::  watersurf_density_ave(ngrid,nslope)             ! Water density at the surface [kg/m^3]
    4545  REAL , INTENT(OUT) ::  watersoil_density(ngrid,nsoilmx,nslope,timelen) ! Water density in the soil layer, time series [kg/m^3]
    46   REAL, INTENT(OUT) ::  TI_ave(ngrid,nsoilmx,nslope)                     ! Average Thermal Inertia  of the concatenated file [SI]
    4746!===============================================================================
    4847!   Local Variables
     
    7170  REAL ::  tsurf_gcm_dyn(iim_input+1,jjm_input+1,nslope,timelen)       ! Surface temperature of the concatenated file, time series [K]
    7271  REAL ::  tsoil_gcm_dyn(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen)! Soil temperature of the concatenated file, time series [K]
    73   REAL ::  TI_gcm(iim_input+1,jjm_input+1,nsoilmx,nslope,timelen)      ! Thermal Inertia  of the concatenated file, times series [SI]
    74   REAL ::  TI_ave_dyn(iim_input+1,jjm_input+1,nsoilmx,nslope)          ! Average Thermal Inertia  of the concatenated file [SI]
    7572  REAL ::  q_co2_dyn(iim_input+1,jjm_input+1,timelen)                  ! CO2 mass mixing ratio in the first layer [kg/m^3]
    7673  REAL ::  q_h2o_dyn(iim_input+1,jjm_input+1,timelen)                  ! H2O mass mixing ratio in the first layer [kg/m^3]
     
    156153
    157154     print *, "Downloading data for tsoil_slope done"
    158      print *, "Downloading data for inertiesoil_slope ..."
    159 
    160 DO islope=1,nslope
    161   write(num,fmt='(i2.2)') islope
    162   call get_var4("inertiesoil_slope"//num,TI_gcm(:,:,:,islope,:))
    163 ENDDO
    164 
    165      print *, "Downloading data for inertiesoil_slope done"
    166155
    167156     print *, "Downloading data for watersoil_density ..."
     
    196185    if(soil_pem) then
    197186      call get_var4("tsoil",tsoil_gcm_dyn(:,:,:,1,:))
    198       call get_var4("inertiesoil",TI_gcm(:,:,:,1,:))
    199187    endif !soil_pem
    200188  endif !nslope=1
     
    221209    print *, "Computing average of tsoil"
    222210    tsoil_ave_dyn(:,:,:,:)=SUM(tsoil_gcm_dyn(:,:,:,:,:),5)/timelen
    223     print *, "Computing average of TI"
    224     TI_ave_dyn(:,:,:,:)=SUM(TI_gcm(:,:,:,:,:),5)/timelen
    225211    print *, "Computing average of watersurf_density"
    226212    watersurf_density_ave(:,:) = SUM(watersurf_density(:,:,:),3)/timelen
     
    269255       CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,min_h2o_ice_dyn(:,:,islope),min_h2o_ice(:,islope))
    270256       if(soil_pem) then
    271          CALL gr_dyn_fi(nsoilmx,iim_input+1,jjm_input+1,ngrid,TI_ave_dyn(:,:,:,islope),TI_ave(:,:,islope))
    272257       DO l=1,nsoilmx
    273258         CALL gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,tsoil_ave_dyn(:,:,l,islope),tsoil_ave(:,l,islope))
  • trunk/LMDZ.COMMON/libf/evolution/update_soil.F90

    r2895 r2937  
    4444   regolith_inertia(:,islope) = inertiedat_PEM(:,1)
    4545   do ig = 1,ngrid
     46      write(*,*) 'ig,islope',ig,islope,tendencies_waterice(ig,islope),waterice(ig,islope)
    4647      if((tendencies_waterice(ig,islope).lt.-1e-5).and.(waterice(ig,islope).eq.0)) then
    4748              regolith_inertia(ig,islope) = inertie_averaged
Note: See TracChangeset for help on using the changeset viewer.