Changeset 3096 for trunk/LMDZ.COMMON/libf
- Timestamp:
- Oct 23, 2023, 4:10:10 PM (14 months ago)
- Location:
- trunk/LMDZ.COMMON/libf/evolution
- Files:
-
- 4 edited
- 3 moved
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/evolution/changelog.txt
r3093 r3096 111 111 == 18/10/2023 == JBC 112 112 The optional file to define the wanted outputs in "diagpem.nc" is now "diagpem.def" (instead of "diagfi.def") + Some updates in the files of deftank. 113 114 == 23/10/2023 == JBC 115 The management of files during the chained simulation of PCM/PEM runs has been simplified: 116 - "tmp_PEMyears.txt" and "info_run_PEM.txt" have been merged into one file called "info_PEM.txt"; 117 - "reshape_XIOS_output.F90" now creates directly the "data_PCM_Y*.nc" files needed by the PEM; 118 - where it is relevant, 'GCM' has been replaced by 'PCM' in the files naming; 119 - the files in deftank have been updated consequently. 120 Following r3095, 'iniorbit' is now a subroutine of "planete_h.F90". -
trunk/LMDZ.COMMON/libf/evolution/conf_pem.F90
r3082 r3096 42 42 43 43 ! #---------- Martian years parameters from launching script 44 open(100,file = ' tmp_PEMyears.txt',status = 'old',form = 'formatted',iostat = ierr)44 open(100,file = 'info_PEM.txt',status = 'old',form = 'formatted',iostat = ierr) 45 45 if (ierr /= 0) then 46 write(*,*) 'Cannot find required file " tmp_PEMyears.txt"!'46 write(*,*) 'Cannot find required file "info_PEM.txt"!' 47 47 write(*,*) 'It should be created by the launching script...' 48 48 stop -
trunk/LMDZ.COMMON/libf/evolution/info_PEM_mod.F90
r3095 r3096 1 MODULE info_ run_PEM_mod1 MODULE info_PEM_mod 2 2 3 3 implicit none … … 7 7 !======================================================================= 8 8 9 SUBROUTINE info_ run_PEM(year_iter,criterion_stop,i_myear,n_myear)9 SUBROUTINE info_PEM(year_iter,criterion_stop,i_myear,n_myear) 10 10 11 11 !======================================================================= 12 12 ! 13 ! Purpose: Write in a file called info_run_PEM.txt the reason why the PEM did stop and the number of extrapolation year done14 ! Update the file tmp_PEMyears.txt to count the number of simulated Martianyears13 ! Purpose: Update the first line of "info_PEM.txt" to count the number of simulated Martian years 14 ! Write in "info_PEM.txt" the reason why the PEM stopped and the number of simulated years 15 15 ! 16 16 ! Author: RV, JBC … … 26 26 27 27 !----- Local variables 28 logical :: ok 28 logical :: ok 29 integer :: cstat 30 character(10) :: ich1, ich2, fch 29 31 30 32 !----- Code 31 inquire(file = 'info_ run_PEM.txt', exist = ok)33 inquire(file = 'info_PEM.txt', exist = ok) 32 34 if (ok) then 33 open(12,file = 'info_run_PEM.txt',status = "old",position = "append",action = "write") 35 write(ich1,'(i0)') i_myear 36 write(ich2,'(i0)') n_myear 37 write(fch,'(f0.4)') convert_years ! 4 digits afetr to the right of the decimal point to respect the precision of Martian year in "launch_pem.sh" 38 call execute_command_line('sed -i "1s/.*/'//trim(ich1)//' '//trim(ich2)//' '//trim(fch)//'/" info_PEM.txt',cmdstat = cstat) 39 if (cstat > 0) then 40 error stop 'info_PEM: command exection failed!' 41 else if (cstat < 0) then 42 error stop 'info_PEM: command execution not supported!' 43 endif 44 open(1,file = 'info_PEM.txt',status = "old",position = "append",action = "write") 45 write(1,*) year_iter, i_myear, criterion_stop 46 close(1) 34 47 else 35 open(12,file = 'info_run_PEM.txt',status = "new",action = "write")48 error stop 'The file ''info_PEM.txt'' does not exist and cannot be updated!' 36 49 endif 37 write(12,*) year_iter, i_myear, criterion_stop38 close(12)39 50 40 open(100,file = 'tmp_PEMyears.txt',status = 'replace') 41 write(100,*) i_myear, n_myear, convert_years 42 close(100) 51 END SUBROUTINE info_PEM 43 52 44 END SUBROUTINE info_run_PEM 45 46 END MODULE info_run_PEM_mod 53 END MODULE info_PEM_mod -
trunk/LMDZ.COMMON/libf/evolution/nb_time_step_PCM_mod.F90
r3095 r3096 1 MODULE nb_time_step_ GCM_mod1 MODULE nb_time_step_PCM_mod 2 2 3 3 use netcdf, only: nf90_open, NF90_NOWRITE, nf90_noerr, nf90_strerror, & … … 13 13 !======================================================================= 14 14 15 SUBROUTINE nb_time_step_ GCM(fichnom,timelen)15 SUBROUTINE nb_time_step_PCM(fichnom,timelen) 16 16 17 17 implicit none … … 19 19 !======================================================================= 20 20 ! 21 ! Purpose: Read in the data_ GCM_Yr*.nc the number of time step21 ! Purpose: Read in the data_PCM_Yr*.nc the number of time step 22 22 ! 23 23 ! Author: RV … … 34 34 integer :: timelen ! number of times stored in the file 35 35 !----------------------------------------------------------------------- 36 modname = "nb_time_step_ GCM"36 modname = "nb_time_step_PCM" 37 37 38 38 ! Open initial state NetCDF file … … 42 42 ierr = nf90_inq_varid (fID, "temps", vID) 43 43 if (ierr /= nf90_noerr) then 44 write(*,*)"read_data_ GCM: Le champ <temps> est absent"45 write(*,*)"read_data_ GCM: J essaie <time_counter>"44 write(*,*)"read_data_PCM: Le champ <temps> est absent" 45 write(*,*)"read_data_PCM: J essaie <time_counter>" 46 46 ierr = nf90_inq_varid (fID, "time_counter", vID) 47 47 if (ierr /= nf90_noerr) then 48 write(*,*)"read_data_ GCM: Le champ <time_counter> est absent"49 write(*,*)"read_data_ GCM: J essaie <Time>"48 write(*,*)"read_data_PCM: Le champ <time_counter> est absent" 49 write(*,*)"read_data_PCM: J essaie <Time>" 50 50 ierr = nf90_inq_varid (fID, "Time", vID) 51 51 if (ierr /= nf90_noerr) then 52 write(*,*)"read_data_ GCM: Le champ <Time> est absent"52 write(*,*)"read_data_PCM: Le champ <Time> est absent" 53 53 write(*,*)trim(nf90_strerror(ierr)) 54 call abort_gcm("nb_time_step_ GCM", "", 1)54 call abort_gcm("nb_time_step_PCM", "", 1) 55 55 endif 56 56 ! Get the length of the "Time" dimension … … 72 72 write(*,*) "The number of timestep of the PCM run data=", timelen 73 73 74 END SUBROUTINE nb_time_step_ GCM74 END SUBROUTINE nb_time_step_PCM 75 75 76 76 !======================================================================= … … 98 98 END SUBROUTINE error_msg 99 99 100 END MODULE nb_time_step_ GCM_mod100 END MODULE nb_time_step_PCM_mod -
trunk/LMDZ.COMMON/libf/evolution/pem.F90
r3088 r3096 4 4 ! I_b READ of start_evol.nc and starfi_evol.nc 5 5 ! I_c Subslope parametrisation 6 ! I_d READ GCM data and convert to the physical grid6 ! I_d READ PCM data and convert to the physical grid 7 7 ! I_e Initialization of the PEM variable and soil 8 8 ! I_f Compute tendencies & Save initial situation … … 48 48 TI_PEM, inertiedat_PEM, & ! soil thermal inertia 49 49 tsoil_PEM, mlayer_PEM, layer_PEM, & ! Soil temp, number of subsurface layers, soil mid layer depths 50 fluxgeo, & ! Geothermal flux for the PEM and GCM50 fluxgeo, & ! Geothermal flux for the PEM and PCM 51 51 water_reservoir ! Water ressources 52 52 use adsorption_mod, only: regolith_adsorption, adsorption_pem, & ! Bool to check if adsorption, main subroutine … … 63 63 use soil_settings_PEM_mod, only: soil_settings_PEM 64 64 use compute_tendencies_slope_mod, only: compute_tendencies_slope 65 use info_ run_PEM_mod, only: info_run_PEM65 use info_PEM_mod, only: info_PEM 66 66 use interpolate_TIPEM_TIGCM_mod, only: interpolate_TIPEM_TIGCM 67 use nb_time_step_ GCM_mod, only: nb_time_step_GCM67 use nb_time_step_PCM_mod, only: nb_time_step_PCM 68 68 use pemetat0_mod, only: pemetat0 69 use read_data_ GCM_mod, only: read_data_GCM69 use read_data_PCM_mod, only: read_data_PCM 70 70 use recomp_tend_co2_slope_mod, only: recomp_tend_co2_slope 71 71 use soil_pem_compute_mod, only: soil_pem_compute … … 83 83 use tracer_mod, only: noms,igcm_h2o_ice, igcm_co2, mmol, igcm_h2o_vap ! Tracer names and molar masses 84 84 use mod_phys_lmdz_para, only: is_parallel, is_sequential, is_mpi_root, is_omp_root, is_master 85 use planete_h, only: aphelie, periheli, year_day, peri_day, obliquit 85 use planete_h, only: aphelie, periheli, year_day, peri_day, obliquit, iniorbit 86 86 use paleoclimate_mod, only: albedo_perenialco2 87 87 use comcstfi_h, only: pi, rad, g, cpp, mugaz, r … … 120 120 parameter(ngridmx = 2 + (jjm - 1)*iim - 1/jjm) 121 121 122 ! Same variable names as in the GCM122 ! Same variable names as in the PCM 123 123 integer, parameter :: nlayer = llm ! Number of vertical layer 124 124 integer :: ngrid ! Number of physical grid points … … 126 126 integer :: day_ini ! First day of the simulation 127 127 real :: pday ! Physical day 128 real :: time_phys ! Same as GCM129 real :: ptimestep ! Same as GCM130 real :: ztime_fin ! Same as GCM128 real :: time_phys ! Same as PCM 129 real :: ptimestep ! Same as PCM 130 real :: ztime_fin ! Same as PCM 131 131 132 132 ! Variables to read start.nc … … 166 166 real :: global_ave_press_new ! constant: Global average pressure of current time step 167 167 real, dimension(:,:), allocatable :: zplev_new ! Physical x Atmospheric field : mass of the atmospheric layers in the pem at current time step [kg/m^2] 168 real, dimension(:,:), allocatable :: zplev_gcm ! same but retrieved from the gcm[kg/m^2]168 real, dimension(:,:), allocatable :: zplev_gcm ! same but retrieved from the PCM [kg/m^2] 169 169 real, dimension(:,:,:), allocatable :: zplev_new_timeseries ! Physical x Atmospheric x Time: same as zplev_new, but in times series [kg/m ^2] 170 170 real, dimension(:,:,:), allocatable :: zplev_old_timeseries ! same but with the time series, for oldest time step … … 175 175 integer :: criterion_stop ! which criterion is reached ? 1= h2o ice surf, 2 = co2 ice surf, 3 = ps, 4 = orb param 176 176 real, save :: A, B, mmean ! Molar mass: intermediate A, B for computations of the mean molar mass of the layer [mol/kg] 177 real, dimension(:,:), allocatable :: vmr_co2_gcm ! Physics x Times co2 volume mixing ratio retrieve from the gcm[m^3/m^3]177 real, dimension(:,:), allocatable :: vmr_co2_gcm ! Physics x Times co2 volume mixing ratio retrieve from the PCM [m^3/m^3] 178 178 real, dimension(:,:), allocatable :: vmr_co2_pem_phys ! Physics x Times co2 volume mixing ratio used in the PEM 179 real, dimension(:,:), allocatable :: q_co2_PEM_phys ! Physics x Times co2 mass mixing ratio in the first layer computed in the PEM, first value comes from GCM [kg/kg]180 real, dimension(:,:), allocatable :: q_h2o_PEM_phys ! Physics x Times: h2o mass mixing ratio computed in the PEM, first value comes from GCM [kg/kg]179 real, dimension(:,:), allocatable :: q_co2_PEM_phys ! Physics x Times co2 mass mixing ratio in the first layer computed in the PEM, first value comes from PCM [kg/kg] 180 real, dimension(:,:), allocatable :: q_h2o_PEM_phys ! Physics x Times: h2o mass mixing ratio computed in the PEM, first value comes from PCM [kg/kg] 181 181 integer :: timelen ! # time samples 182 182 real :: ave ! intermediate varibale to compute average … … 189 189 real, dimension(:,:), allocatable :: min_h2o_ice_1 ! ngrid field: minimum of water ice at each point for the first year [kg/m^2] 190 190 real, dimension(:,:), allocatable :: min_h2o_ice_2 ! ngrid field: minimum of water ice at each point for the second year [kg/m^2] 191 real, dimension(:,:,:), allocatable :: co2_ice_GCM ! Physics x NSLOPE x Times field: co2 ice given by the GCM [kg/m^2]191 real, dimension(:,:,:), allocatable :: co2_ice_GCM ! Physics x NSLOPE x Times field: co2 ice given by the PCM [kg/m^2] 192 192 real, dimension(:,:), allocatable :: initial_co2_ice_sublim ! physical point field: Logical array indicating sublimating point of co2 ice 193 193 real, dimension(:,:), allocatable :: initial_h2o_ice ! physical point field: Logical array indicating if there is water ice at initial state 194 194 real, dimension(:,:), allocatable :: initial_co2_ice ! physical point field: Logical array indicating if there is co2 ice at initial state 195 195 real, dimension(:,:), allocatable :: tendencies_co2_ice ! physical point x slope field: Tendency of evolution of perenial co2 ice over a year 196 real, dimension(:,:), allocatable :: tendencies_co2_ice_ini ! physical point x slope field x nslope: Tendency of evolution of perenial co2 ice over a year in the GCM196 real, dimension(:,:), allocatable :: tendencies_co2_ice_ini ! physical point x slope field x nslope: Tendency of evolution of perenial co2 ice over a year in the PCM 197 197 real, dimension(:,:), allocatable :: tendencies_h2o_ice ! physical point x slope field: Tendency of evolution of perenial h2o ice 198 198 real, dimension(:,:), allocatable :: flag_co2flow ! (ngrid,nslope): Flag where there is a CO2 glacier flow … … 207 207 real, dimension(:,:,:,:), allocatable :: tsoil_phys_PEM_timeseries ! IG x SLOPE XTULES field : NOn averaged Soil Temperature [K] 208 208 real, dimension(:,:,:,:), allocatable :: tsoil_GCM_timeseries ! IG x SLOPE XTULES field : NOn averaged Soil Temperature [K] 209 real, dimension(:,:), allocatable :: tsurf_ave_yr1 ! Physic x SLOPE field : Averaged Surface Temperature of first call of the gcm[K]209 real, dimension(:,:), allocatable :: tsurf_ave_yr1 ! Physic x SLOPE field : Averaged Surface Temperature of first call of the PCM [K] 210 210 real, dimension(:,:), allocatable :: TI_locslope ! Physic x Soil: Intermediate thermal inertia to compute Tsoil [SI] 211 211 real, dimension(:,:), allocatable :: Tsoil_locslope ! Physic x Soil: intermediate when computing Tsoil [K] … … 346 346 #endif 347 347 348 ! In the gcm, these values are given to the physic by the dynamic.348 ! In the PCM, these values are given to the physic by the dynamic. 349 349 ! Here we simply read them in the startfi_evol.nc file 350 350 status = nf90_open(FILE_NAME, NF90_NOWRITE, ncid) … … 459 459 !------------------------ 460 460 ! I Initialization 461 ! I_d READ GCM data and convert to the physical grid462 !------------------------ 463 ! First we read the evolution of water and co2 ice (and the mass mixing ratio) over the first year of the GCM run, saving only the minimum value464 call nb_time_step_ GCM("data_GCM_Y1.nc",timelen)461 ! I_d READ PCM data and convert to the physical grid 462 !------------------------ 463 ! First we read the evolution of water and co2 ice (and the mass mixing ratio) over the first year of the PCM run, saving only the minimum value 464 call nb_time_step_PCM("data_PCM_Y1.nc",timelen) 465 465 466 466 allocate(tsoil_ave(ngrid,nsoilmx,nslope)) … … 491 491 492 492 write(*,*) "Downloading data Y1..." 493 call read_data_ GCM("data_GCM_Y1.nc",timelen, iim,jjm_value,ngrid,nslope,vmr_co2_gcm,ps_timeseries,min_co2_ice_1,min_h2o_ice_1, &493 call read_data_PCM("data_PCM_Y1.nc",timelen, iim,jjm_value,ngrid,nslope,vmr_co2_gcm,ps_timeseries,min_co2_ice_1,min_h2o_ice_1, & 494 494 tsurf_ave_yr1,tsoil_ave, tsurf_GCM_timeseries,tsoil_GCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, & 495 495 co2_ice_GCM,watersurf_density_ave,watersoil_density_timeseries) 496 496 write(*,*) "Downloading data Y1 done" 497 497 498 ! Then we read the evolution of water and co2 ice (and the mass mixing ratio) over the second year of the GCM run, saving only the minimum value498 ! Then we read the evolution of water and co2 ice (and the mass mixing ratio) over the second year of the PCM run, saving only the minimum value 499 499 write(*,*) "Downloading data Y2" 500 call read_data_ GCM("data_GCM_Y2.nc",timelen,iim,jjm_value,ngrid,nslope,vmr_co2_gcm,ps_timeseries,min_co2_ice_2,min_h2o_ice_2, &500 call read_data_PCM("data_PCM_Y2.nc",timelen,iim,jjm_value,ngrid,nslope,vmr_co2_gcm,ps_timeseries,min_co2_ice_2,min_h2o_ice_2, & 501 501 tsurf_ave,tsoil_ave, tsurf_GCM_timeseries,tsoil_GCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, & 502 502 co2_ice_GCM,watersurf_density_ave,watersoil_density_timeseries) … … 1068 1068 enddo 1069 1069 1070 ! Conserving the tracers mass for GCM start files1070 ! Conserving the tracers mass for PCM start files 1071 1071 do nnq = 1,nqtot 1072 1072 do ig = 1,ngrid … … 1139 1139 write(*,*) "restartpem.nc has been written" 1140 1140 1141 call info_ run_PEM(year_iter,criterion_stop,i_myear,n_myear)1141 call info_PEM(year_iter,criterion_stop,i_myear,n_myear) 1142 1142 1143 1143 write(*,*) "The PEM has run for", year_iter, "Martian years." -
trunk/LMDZ.COMMON/libf/evolution/read_data_PCM_mod.F90
r3095 r3096 1 MODULE read_data_ GCM_mod1 MODULE read_data_PCM_mod 2 2 3 3 use netcdf, only: nf90_open, NF90_NOWRITE, nf90_noerr, nf90_strerror, & … … 14 14 !======================================================================= 15 15 16 SUBROUTINE read_data_ GCM(fichnom,timelen,iim_input,jjm_input,ngrid,nslope,vmr_co2_gcm_phys,ps_timeseries, &16 SUBROUTINE read_data_PCM(fichnom,timelen,iim_input,jjm_input,ngrid,nslope,vmr_co2_gcm_phys,ps_timeseries, & 17 17 min_co2_ice,min_h2o_ice,tsurf_ave,tsoil_ave,tsurf_gcm,tsoil_gcm,q_co2,q_h2o,co2_ice_slope, & 18 18 watersurf_density_ave,watersoil_density) … … 25 25 !======================================================================= 26 26 ! 27 ! Purpose: Read initial confitions file from the GCM27 ! Purpose: Read initial confitions file from the PCM 28 28 ! 29 29 ! Authors: RV & LL … … 41 41 real, dimension(ngrid,nslope), intent(out) :: min_co2_ice ! Minimum of co2 ice per slope of the year [kg/m^2] 42 42 real, dimension(ngrid,nslope), intent(out) :: min_h2o_ice ! Minimum of h2o ice per slope of the year [kg/m^2] 43 real, dimension(ngrid,timelen), intent(out) :: vmr_co2_gcm_phys ! Physics x Times co2 volume mixing ratio retrieve from the gcm[m^3/m^3]43 real, dimension(ngrid,timelen), intent(out) :: vmr_co2_gcm_phys ! Physics x Times co2 volume mixing ratio retrieve from the PCM [m^3/m^3] 44 44 real, dimension(ngrid,timelen), intent(out) :: ps_timeseries ! Surface Pressure [Pa] 45 45 real, dimension(ngrid,timelen), intent(out) :: q_co2 ! CO2 mass mixing ratio in the first layer [kg/m^3] … … 81 81 82 82 !----------------------------------------------------------------------- 83 modname="read_data_ gcm"83 modname="read_data_PCM" 84 84 85 85 A = (1/m_co2 - 1/m_noco2) … … 280 280 #endif 281 281 282 END SUBROUTINE read_data_ gcm282 END SUBROUTINE read_data_PCM 283 283 284 284 SUBROUTINE check_dim(n1,n2,str1,str2) … … 366 366 END SUBROUTINE error_msg 367 367 368 END MODULE read_data_ GCM_mod368 END MODULE read_data_PCM_mod -
trunk/LMDZ.COMMON/libf/evolution/reshape_XIOS_output.F90
r3076 r3096 3 3 !======================================================================= 4 4 ! 5 ! Purpose: Read XIOS files, and convert them into the correct GCM grid5 ! Purpose: Read XIOS files, and convert them into the correct PCM grid 6 6 ! XIOS longitudes start at -180 but stop before -180 (not duplicated) 7 7 ! We basically add the last point, and complete the XIOS file. Looped 8 ! over the two GCM runs8 ! over the two PCM runs 9 9 ! 10 10 ! Authors: RV & LL … … 35 35 if (state /= nf90_noerr) call handle_err(state) 36 36 37 state = nf90_create(path = "data reshaped"//str2//".nc", cmode=or(nf90_noclobber,nf90_64bit_offset), ncid = ncid2)37 state = nf90_create(path = "data_PCM_Y"//str2//".nc", cmode=or(nf90_noclobber,nf90_64bit_offset), ncid = ncid2) 38 38 if (state /= nf90_noerr) call handle_err(state) 39 39
Note: See TracChangeset
for help on using the changeset viewer.