Changeset 3367 for trunk/LMDZ.COMMON
- Timestamp:
- Jun 11, 2024, 5:15:20 PM (5 months ago)
- Location:
- trunk/LMDZ.COMMON/libf/evolution
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/evolution/changelog.txt
r3366 r3367 349 349 Some features might not work very well yet since not every stituation has not been tested. 350 350 351 == 10/06/2024 == JBC 352 - The PEM can now stop itself cleanly before the SLURM time limit for the job is reached and it continues the simulation with a new cycle. 353 - Update of "jobPEM.slurm" in the deftank to guarantee enough memory space to run the job. 354 - Few minor cleanings. 355 356 == 10/06/2024 == JBC 357 Correction of an error in "lib_launchPEM.sh" due to a miscalculated condition + Improvement of the relaunch which now cleans the unnecessary files. 358 351 359 == 11/06/2024 == LL 352 360 Fixing bug in the initial computation of ice tendencies (a negative tendancies was computed when a glacier was disapearing at the end of the second year of the PCM). 353 361 Fixing a bug in the update of the tendencies of CO2 to ensure mass conservation 354 362 355 ~ 363 == 11/06/2024 == JBC 364 Removal of useless condition and variable + some updates. -
trunk/LMDZ.COMMON/libf/evolution/compute_tend_mod.F90
r3366 r3367 13 13 !======================================================================= 14 14 ! 15 ! Compute the initial tendencies of the evolution icebased on the PCM data15 ! Compute the initial tendencies of the ice evolution based on the PCM data 16 16 ! 17 17 !======================================================================= … … 33 33 where (abs(tendencies_ice) < 1.e-10) tendencies_ice = 0. 34 34 35 ! If the minimum over the last year is 0 then we have no perennial ice35 ! If the minimum over the last year is 0, then we have no perennial ice 36 36 where (abs(min_ice(:,:,2)) < 1.e-10) tendencies_ice = 0. 37 37 38 END SUBROUTINE compute_tend 38 39 -
trunk/LMDZ.COMMON/libf/evolution/deftank/lib_launchPEM.sh
r3365 r3367 253 253 i_myear=$irelaunch 254 254 sed -i "1s/.*/$i_myear $n_myear $convert_years $iPCM $iPEM $nPCM $nPCM_ini/" info_PEM.txt 255 rm -f startpem.nc 255 256 if [ $irelaunch -eq $(($nPCM_ini - 1)) ]; then 256 257 cp diags/data2reshape${irelaunch}.nc data2reshape_Y1.nc -
trunk/LMDZ.COMMON/libf/evolution/evol_ice_mod.F90
r3366 r3367 29 29 ! local: 30 30 ! ------ 31 real, dimension(ngrid,nslope) :: co2_ice_tmp ! Evolution of perennial ice over one year31 real, dimension(ngrid,nslope), intent(inout) :: co2_ice_old ! Old density of CO2 ice 32 32 !======================================================================= 33 33 ! Evolution of CO2 ice for each physical point 34 34 write(*,*) 'Evolution of co2 ice' 35 co2_ice_tmp = co2_ice + tend_co2_ice*dt_pem 36 where (co2_ice_tmp < 0.) 37 co2_ice_tmp = 0. 38 tend_co2_ice = -co2_ice/dt_pem 35 36 co2_ice_old = co2_ice 37 co2_ice = co2_ice + tend_co2_ice*dt_pem 38 where (co2_ice < 0.) 39 co2_ice = 0. 40 tend_co2_ice = -co2_ice_old/dt_pem 39 41 end where 40 co2_ice = co2_ice_tmp 42 41 43 END SUBROUTINE evol_co2_ice 42 44 -
trunk/LMDZ.COMMON/libf/evolution/pem.F90
r3365 r3367 193 193 194 194 ! Variables for slopes 195 real, dimension(:,:,:), allocatable :: co2_ice_PCM ! Physics x slope x Times field: co2 ice given by the PCM [kg/m^2]196 195 real, dimension(:,:), allocatable :: tend_co2_ice ! physical point x slope field: Tendency of evolution of perennial co2 ice over a year 197 196 real, dimension(:,:), allocatable :: tend_co2_ice_ini ! physical point x slope field: Tendency of evolution of perennial co2 ice over a year in the PCM … … 203 202 204 203 ! Variables for surface and soil 205 real, dimension(:,:), allocatable :: tsurf_av e! Physic x SLOPE field: Averaged Surface Temperature [K]206 real, dimension(:,:,:), allocatable :: tsoil_av e! Physic x SOIL x SLOPE field: Averaged Soil Temperature [K]204 real, dimension(:,:), allocatable :: tsurf_avg ! Physic x SLOPE field: Averaged Surface Temperature [K] 205 real, dimension(:,:,:), allocatable :: tsoil_avg ! Physic x SOIL x SLOPE field: Averaged Soil Temperature [K] 207 206 real, dimension(:,:,:), allocatable :: tsoil_anom ! Amplitude between instataneous and yearly average soil temperature [K] 208 207 real, dimension(:,:,:), allocatable :: tsurf_PCM_timeseries ! ngrid x SLOPE x TIMES field: Surface Temperature in timeseries [K] … … 214 213 real, dimension(:), allocatable :: Tsurf_locslope ! Physic x Soil: Intermediate surface temperature to compute Tsoil [K] 215 214 real, dimension(:,:,:,:), allocatable :: watersoil_density_timeseries ! Physic x Soil x Slope x Times water soil density, time series [kg /m^3] 216 real, dimension(:,:), allocatable :: watersurf_density_av e! Physic x Slope, water surface density, yearly averaged [kg/m^3]215 real, dimension(:,:), allocatable :: watersurf_density_avg ! Physic x Slope, water surface density, yearly averaged [kg/m^3] 217 216 real, dimension(:,:,:,:), allocatable :: watersoil_density_PEM_timeseries ! Physic x Soil x Slope x Times, water soil density, time series [kg/m^3] 218 real, dimension(:,:,:), allocatable :: watersoil_density_PEM_av e! Physic x Soil x Slopes, water soil density, yearly averaged [kg/m^3]217 real, dimension(:,:,:), allocatable :: watersoil_density_PEM_avg ! Physic x Soil x Slopes, water soil density, yearly averaged [kg/m^3] 219 218 real, dimension(:,:), allocatable :: Tsurfavg_before_saved ! Surface temperature saved from previous time step [K] 220 219 real, dimension(:), allocatable :: delta_co2_adsorbded ! Physics: quantity of CO2 that is exchanged because of adsorption / desorption [kg/m^2] … … 521 520 call nb_time_step_PCM("data_PCM_Y1.nc",timelen) 522 521 523 allocate(tsoil_av e(ngrid,nsoilmx,nslope))524 allocate(watersoil_density_PEM_av e(ngrid,nsoilmx_PEM,nslope))522 allocate(tsoil_avg(ngrid,nsoilmx,nslope)) 523 allocate(watersoil_density_PEM_avg(ngrid,nsoilmx_PEM,nslope)) 525 524 allocate(vmr_co2_PCM(ngrid,timelen)) 526 525 allocate(ps_timeseries(ngrid,timelen)) … … 528 527 allocate(min_h2o_ice(ngrid,nslope,2)) 529 528 allocate(tsurf_avg_yr1(ngrid,nslope)) 530 allocate(tsurf_av e(ngrid,nslope))529 allocate(tsurf_avg(ngrid,nslope)) 531 530 allocate(tsurf_PCM_timeseries(ngrid,nslope,timelen)) 532 531 allocate(tsoil_PCM_timeseries(ngrid,nsoilmx,nslope,timelen)) 533 532 allocate(q_co2_PEM_phys(ngrid,timelen)) 534 533 allocate(q_h2o_PEM_phys(ngrid,timelen)) 535 allocate(co2_ice_PCM(ngrid,nslope,timelen)) 536 allocate(watersurf_density_ave(ngrid,nslope)) 534 allocate(watersurf_density_avg(ngrid,nslope)) 537 535 allocate(watersoil_density_timeseries(ngrid,nsoilmx,nslope,timelen)) 538 536 allocate(Tsurfavg_before_saved(ngrid,nslope)) … … 548 546 write(*,*) "Downloading data Y1..." 549 547 call read_data_PCM("data_PCM_Y1.nc",timelen,iim,jjm_value,ngrid,nslope,vmr_co2_PCM,ps_timeseries,min_co2_ice(:,:,1),min_h2o_ice(:,:,1), & 550 tsurf_avg_yr1,tsoil_av e,tsurf_PCM_timeseries,tsoil_PCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, &551 co2_ice_PCM,watersurf_density_ave,watersoil_density_timeseries)548 tsurf_avg_yr1,tsoil_avg,tsurf_PCM_timeseries,tsoil_PCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, & 549 watersurf_density_avg,watersoil_density_timeseries) 552 550 write(*,*) "Downloading data Y1 done!" 553 551 … … 555 553 write(*,*) "Downloading data Y2..." 556 554 call read_data_PCM("data_PCM_Y2.nc",timelen,iim,jjm_value,ngrid,nslope,vmr_co2_PCM,ps_timeseries,min_co2_ice(:,:,2),min_h2o_ice(:,:,2), & 557 tsurf_av e,tsoil_ave,tsurf_PCM_timeseries,tsoil_PCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, &558 co2_ice_PCM,watersurf_density_ave,watersoil_density_timeseries)555 tsurf_avg,tsoil_avg,tsurf_PCM_timeseries,tsoil_PCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, & 556 watersurf_density_avg,watersoil_density_timeseries) 559 557 write(*,*) "Downloading data Y2 done!" 560 558 … … 572 570 if (soil_pem) then 573 571 allocate(tsoil_anom(ngrid,nsoilmx,nslope)) 574 tsoil_anom = tsoil - tsoil_av e! compute anomaly between Tsoil(t) in the startfi - <Tsoil> to recompute properly tsoil in the restart572 tsoil_anom = tsoil - tsoil_avg ! compute anomaly between Tsoil(t) in the startfi - <Tsoil> to recompute properly tsoil in the restart 575 573 call soil_settings_PEM(ngrid,nslope,nsoilmx_PEM,nsoilmx,inertiesoil,TI_PEM) 576 tsoil_PEM(:,1:nsoilmx,:) = tsoil_av e574 tsoil_PEM(:,1:nsoilmx,:) = tsoil_avg 577 575 tsoil_phys_PEM_timeseries(:,1:nsoilmx,:,:) = tsoil_PCM_timeseries 578 576 watersoil_density_PEM_timeseries(:,1:nsoilmx,:,:) = watersoil_density_timeseries 579 577 do l = nsoilmx + 1,nsoilmx_PEM 580 tsoil_PEM(:,l,:) = tsoil_av e(:,nsoilmx,:)578 tsoil_PEM(:,l,:) = tsoil_avg(:,nsoilmx,:) 581 579 watersoil_density_PEM_timeseries(:,l,:,:) = watersoil_density_timeseries(:,nsoilmx,:,:) 582 580 enddo 583 watersoil_density_PEM_av e= sum(watersoil_density_PEM_timeseries,4)/timelen581 watersoil_density_PEM_avg = sum(watersoil_density_PEM_timeseries,4)/timelen 584 582 endif !soil_pem 585 deallocate(tsoil_av e,tsoil_PCM_timeseries)583 deallocate(tsoil_avg,tsoil_PCM_timeseries) 586 584 587 585 !------------------------ … … 614 612 615 613 call pemetat0("startpem.nc",ngrid,nsoilmx,nsoilmx_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,porefillingice_depth, & 616 porefillingice_thickness,tsurf_avg_yr1,tsurf_av e,q_co2_PEM_phys,q_h2o_PEM_phys,ps_timeseries, &614 porefillingice_thickness,tsurf_avg_yr1,tsurf_avg,q_co2_PEM_phys,q_h2o_PEM_phys,ps_timeseries, & 617 615 tsoil_phys_PEM_timeseries,tend_h2o_ice,tend_co2_ice,co2_ice,h2o_ice,global_avg_press_PCM, & 618 watersurf_density_av e,watersoil_density_PEM_ave,co2_adsorbded_phys,delta_co2_adsorbded, &616 watersurf_density_avg,watersoil_density_PEM_avg,co2_adsorbded_phys,delta_co2_adsorbded, & 619 617 h2o_adsorbded_phys,delta_h2o_adsorbded,stratif) 620 618 … … 822 820 if (co2ice_flow .and. nslope > 1) call flow_co2glaciers(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,vmr_co2_PEM_phys,ps_timeseries, & 823 821 global_avg_press_PCM,global_avg_press_new,co2_ice,flag_co2flow,flag_co2flow_mesh) 824 if (h2oice_flow .and. nslope > 1) call flow_h2oglaciers(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,tsurf_av e,h2o_ice,flag_h2oflow,flag_h2oflow_mesh)822 if (h2oice_flow .and. nslope > 1) call flow_h2oglaciers(timelen,ngrid,nslope,iflat,subslope_dist,def_slope_mean,tsurf_avg,h2o_ice,flag_h2oflow,flag_h2oflow_mesh) 825 823 826 824 !------------------------ … … 831 829 write(*,*) "Updating the new Tsurf" 832 830 bool_sublim = .false. 833 Tsurfavg_before_saved = tsurf_av e831 Tsurfavg_before_saved = tsurf_avg 834 832 do ig = 1,ngrid 835 833 do islope = 1,nslope … … 840 838 do islope_loop = islope,iflat,-1 841 839 if (.not. is_co2ice_ini(ig_loop,islope_loop) .and. co2_ice(ig_loop,islope_loop) < 1.e-10) then 842 tsurf_av e(ig,islope) = tsurf_ave(ig_loop,islope_loop)840 tsurf_avg(ig,islope) = tsurf_avg(ig_loop,islope_loop) 843 841 bool_sublim = .true. 844 842 exit … … 851 849 do islope_loop = islope,iflat 852 850 if (.not. is_co2ice_ini(ig_loop,islope_loop) .and. co2_ice(ig_loop,islope_loop) < 1.e-10) then 853 tsurf_av e(ig,islope) = tsurf_ave(ig_loop,islope_loop)851 tsurf_avg(ig,islope) = tsurf_avg(ig_loop,islope_loop) 854 852 bool_sublim = .true. 855 853 exit … … 870 868 ave = 0. 871 869 do t = 1,timelen 872 if (co2_ice_PCM(ig,islope,t) > 1.e-3) then 873 ave = ave + beta_clap_co2/(alpha_clap_co2 - log(vmr_co2_PEM_phys(ig,t)*ps_timeseries(ig,t)/100.)) 874 else 875 ave = ave + tsurf_PCM_timeseries(ig,islope,t) 876 endif 870 ave = ave + beta_clap_co2/(alpha_clap_co2 - log(vmr_co2_PEM_phys(ig,t)*ps_timeseries(ig,t)/100.)) 877 871 enddo 878 tsurf_av e(ig,islope) = ave/timelen872 tsurf_avg(ig,islope) = ave/timelen 879 873 endif 880 874 enddo … … 882 876 883 877 do t = 1,timelen 884 tsurf_PCM_timeseries(:,:,t) = tsurf_PCM_timeseries(:,:,t) + tsurf_av e- Tsurfavg_before_saved878 tsurf_PCM_timeseries(:,:,t) = tsurf_PCM_timeseries(:,:,t) + tsurf_avg - Tsurfavg_before_saved 885 879 enddo 886 880 ! for the start 887 881 do ig = 1,ngrid 888 882 do islope = 1,nslope 889 tsurf(ig,islope) = tsurf(ig,islope) - (Tsurfavg_before_saved(ig,islope) - tsurf_av e(ig,islope))883 tsurf(ig,islope) = tsurf(ig,islope) - (Tsurfavg_before_saved(ig,islope) - tsurf_avg(ig,islope)) 890 884 enddo 891 885 enddo … … 917 911 enddo 918 912 tsoil_PEM = sum(tsoil_phys_PEM_timeseries,4)/timelen 919 watersoil_density_PEM_av e= sum(watersoil_density_PEM_timeseries,4)/timelen913 watersoil_density_PEM_avg = sum(watersoil_density_PEM_timeseries,4)/timelen 920 914 921 915 write(*,*) "Update of soil temperature done" … … 927 921 write(*,*) "Compute ice table" 928 922 porefillingice_thickness_prev_iter = porefillingice_thickness 929 call computeice_table_equilibrium(ngrid,nslope,nsoilmx_PEM,watercaptag,watersurf_density_av e,watersoil_density_PEM_ave,TI_PEM(:,1,:),porefillingice_depth,porefillingice_thickness)930 call compute_massh2o_exchange_ssi(ngrid,nslope,nsoilmx_PEM,porefillingice_thickness_prev_iter,porefillingice_thickness,porefillingice_depth,tsurf_av e, tsoil_PEM,delta_h2o_icetablesublim) ! Mass of H2O exchange between the ssi and the atmosphere923 call computeice_table_equilibrium(ngrid,nslope,nsoilmx_PEM,watercaptag,watersurf_density_avg,watersoil_density_PEM_avg,TI_PEM(:,1,:),porefillingice_depth,porefillingice_thickness) 924 call compute_massh2o_exchange_ssi(ngrid,nslope,nsoilmx_PEM,porefillingice_thickness_prev_iter,porefillingice_thickness,porefillingice_depth,tsurf_avg, tsoil_PEM,delta_h2o_icetablesublim) ! Mass of H2O exchange between the ssi and the atmosphere 931 925 endif 932 926 ! II_d.4 Update the soil thermal properties … … 967 961 ! II_e Outputs 968 962 !------------------------ 969 call writediagpem(ngrid,'ps_av e','Global average pressure','Pa',0,(/global_avg_press_new/))963 call writediagpem(ngrid,'ps_avg','Global average pressure','Pa',0,(/global_avg_press_new/)) 970 964 do islope = 1,nslope 971 965 write(str2(1:2),'(i2.2)') islope … … 1202 1196 endif 1203 1197 deallocate(vmr_co2_PCM,ps_timeseries,tsurf_PCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys) 1204 deallocate( co2_ice_PCM,watersurf_density_ave,watersoil_density_timeseries,Tsurfavg_before_saved)1205 deallocate(tsoil_phys_PEM_timeseries,watersoil_density_PEM_timeseries,watersoil_density_PEM_av e)1198 deallocate(watersurf_density_avg,watersoil_density_timeseries,Tsurfavg_before_saved) 1199 deallocate(tsoil_phys_PEM_timeseries,watersoil_density_PEM_timeseries,watersoil_density_PEM_avg) 1206 1200 deallocate(delta_co2_adsorbded,delta_h2o_adsorbded,vmr_co2_PEM_phys,delta_h2o_icetablesublim,porefillingice_thickness_prev_iter) 1207 1201 deallocate(is_co2ice_ini,co2ice_disappeared,ini_co2ice_sublim,ini_h2oice_sublim,stratif) -
trunk/LMDZ.COMMON/libf/evolution/read_data_PCM_mod.F90
r3363 r3367 15 15 !======================================================================= 16 16 17 SUBROUTINE read_data_PCM(filename,timelen,iim_input,jjm_input,ngrid,nslope,vmr_co2_PCM_phys,ps_timeseries, 18 min_co2_ice,min_h2o_ice,tsurf_avg,tsoil_avg,tsurf_PCM,tsoil_PCM,q_co2,q_h2o, co2_ice_slope,&17 SUBROUTINE read_data_PCM(filename,timelen,iim_input,jjm_input,ngrid,nslope,vmr_co2_PCM_phys,ps_timeseries, & 18 min_co2_ice,min_h2o_ice,tsurf_avg,tsoil_avg,tsurf_PCM,tsoil_PCM,q_co2,q_h2o, & 19 19 watersurf_density_avg,watersoil_density) 20 20 use comsoil_h, only: nsoilmx … … 45 45 real, dimension(ngrid,timelen), intent(out) :: q_co2 ! CO2 mass mixing ratio in the first layer [kg/m^3] 46 46 real, dimension(ngrid,timelen), intent(out) :: q_h2o ! H2O mass mixing ratio in the first layer [kg/m^3] 47 real, dimension(ngrid,nslope,timelen), intent(out) :: co2_ice_slope ! co2 ice amount per slope of the year [kg/m^2]48 47 !SOIL 49 48 real, dimension(ngrid,nslope), intent(out) :: tsurf_avg ! Average surface temperature of the concatenated file [K] … … 72 71 real, dimension(iim_input + 1,jjm_input + 1,timelen) :: q_co2_dyn ! CO2 mass mixing ratio in the first layer [kg/m^3] 73 72 real, dimension(iim_input + 1,jjm_input + 1,timelen) :: q_h2o_dyn ! H2O mass mixing ratio in the first layer [kg/m^3] 74 real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen) :: co2_ice_slope_dyn ! co2 ice amount per 73 real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen) :: co2_ice_slope_dyn ! co2 ice amount per slope of the year [kg/m^2] 75 74 real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen) :: watersurf_density_dyn ! Water density at the surface, time series [kg/m^3] 76 75 real, dimension(iim_input + 1,jjm_input + 1,nslope) :: watersurf_density_dyn_avg ! Water density at the surface, dynamic grid, yearly averaged [kg/m^3] … … 239 238 do t = 1,timelen 240 239 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,tsurf_PCM_dyn(:,:,islope,t),tsurf_PCM(:,islope,t)) 241 call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,co2_ice_slope_dyn(:,:,islope,t),co2_ice_slope(:,islope,t))242 240 enddo 243 241 enddo … … 258 256 endif ! soil_pem 259 257 tsurf_PCM(1,:,:) = tsurf_PCM_dyn(1,1,:,:) 260 co2_ice_slope(1,:,:) = co2_ice_slope_dyn(1,1,:,:)261 258 tsurf_avg(1,:) = tsurf_avg_dyn(1,1,:) 262 259 #endif
Note: See TracChangeset
for help on using the changeset viewer.