- Timestamp:
- Nov 12, 2024, 6:35:33 PM (9 days ago)
- Location:
- trunk/LMDZ.COMMON/libf/evolution
- Files:
-
- 8 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/evolution/NS_dyn_ss_ice_m.F90
r3493 r3512 9 9 !!! 10 10 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 11 12 13 11 14 12 SUBROUTINE dyn_ss_ice_m(ssi_depth_in,T1,Tb,nz,thIn,p0,pfrost,porefill_in,porefill,ssi_depth) … … 69 67 !call setgrid(nz,z,zmax,zfac) 70 68 l1=2.e-4 71 do iloop=0,nz 72 z(iloop ) = l1*(1+iloop**2.9*(1-exp(-real(iloop)/20.)))69 do iloop=0,nz - 1 70 z(iloop + 1) = l1*(1+iloop**2.9*(1-exp(-real(iloop)/20.))) 73 71 enddo 74 72 -
trunk/LMDZ.COMMON/libf/evolution/NS_fast_subs_mars.F90
r3493 r3512 116 116 call icechanges(nz,z(:),typeF,avdrho(k),avdrhoP(k),ypp(:), & 117 117 & Diff,porosity,icefrac,bigstep,zdepthT(k),porefill(:,k),typeG) 118 118 if (typeP>2) then 119 119 if (mode2 .and. porefill(typeP,k)>=1. .and. porefill(typeP-1,k)==0.) then ! nothing changed 120 120 porefill(typeP-1,k)=1. ! paste a layer 121 121 ! write(34,*) '# mode 2 growth occurred',typeP,typeF,typeT 122 endif 122 123 endif 123 124 -
trunk/LMDZ.COMMON/libf/evolution/changelog.txt
r3498 r3512 477 477 - Renaming of the tendencies in the PEM with the prefix 'd_' instead of 'tend_'; 478 478 - Modification of the PEM time step type from integer to real. As a consequence, all time variables are now of real type. This change adds the possibility to consider fractions of year as time step. 479 480 == 12/11/2024 == JBC 481 Few corrections related to r3498 (time step from integer to real) and r3493 (Norbert Schorghofer's subroutines for dynamic ice table) in order to make the code work properly. -
trunk/LMDZ.COMMON/libf/evolution/ice_table_mod.F90
r3498 r3512 28 28 29 29 allocate(icetable_depth(ngrid,nslope)) 30 if (icetable_equilibrium) then 31 allocate(icetable_thickness(ngrid,nslope)) 32 else if (icetable_dynamic) then 33 allocate(ice_porefilling(ngrid,nsoil,nslope)) 34 endif 30 allocate(icetable_thickness(ngrid,nslope)) 31 allocate(ice_porefilling(ngrid,nsoil,nslope)) 35 32 36 33 END SUBROUTINE ini_ice_table -
trunk/LMDZ.COMMON/libf/evolution/info_PEM_mod.F90
r3498 r3512 31 31 logical :: ok 32 32 integer :: cstat 33 character(10) :: ich1, ich2, ich3, ich4, ich5, ich6, fch 33 character(10) :: frmt 34 character(20) :: ich1, ich2, ich3, ich4, fch1, fch2, fch3 34 35 35 36 !----- Code 36 37 inquire(file = 'info_PEM.txt',exist = ok) 37 38 if (ok) then 38 write( ich1,'(f0.4)') i_myear39 write( ich2,'(f0.4)') n_myear40 write(fch ,'(f0.4)') convert_years ! 4 digits to the right of the decimal point to respect the precision of Martian year in "launch_pem.sh"41 write(ich 3,'(i0)') iPCM42 write(ich 4,'(i0)') iPEM + 143 write(ich 5,'(i0)') nPCM44 write(ich 6,'(i0)') nPCM_ini45 call execute_command_line('sed -i "1s/.*/'//trim( ich1)//' '//trim(ich2)//' '//trim(fch)//' '//trim(ich3)//' '//trim(ich4)//' '//trim(ich5)//' '//trim(ich6)//'/" info_PEM.txt',cmdstat = cstat)39 write(fch1,'(f'//int2str(nb_digits(i_myear) + 5)//'.4)') i_myear 40 write(fch2,'(f'//int2str(nb_digits(n_myear) + 5)//'.4)') n_myear 41 write(fch3,'(f6.4)') convert_years ! 4 digits to the right of the decimal point to respect the precision of Martian year in "launch_pem.sh" 42 write(ich1,'(i0)') iPCM 43 write(ich2,'(i0)') iPEM + 1 44 write(ich3,'(i0)') nPCM 45 write(ich4,'(i0)') nPCM_ini 46 call execute_command_line('sed -i "1s/.*/'//trim(fch1)//' '//trim(fch2)//' '//trim(fch3)//' '//trim(ich1)//' '//trim(ich2)//' '//trim(ich3)//' '//trim(ich4)//'/" info_PEM.txt',cmdstat = cstat) 46 47 if (cstat > 0) then 47 48 error stop 'info_PEM: command execution failed!' … … 60 61 END SUBROUTINE info_PEM 61 62 63 !======================================================================= 64 65 FUNCTION int2str(i) RESULT(str) 66 ! Function to convert an integer into a string 67 68 integer, intent(in) :: i 69 character(20) :: str 70 71 if (nb_digits(real(i)) > len(str)) error stop 'int2str [info_PEM_mod]: invalid integer for conversion!' 72 write(str,'(i0)') i 73 str = trim(adjustl(str)) 74 75 END FUNCTION int2str 76 77 !======================================================================= 78 79 FUNCTION nb_digits(x) RESULT(idigits) 80 ! Function to give the number of digits for the integer part of a real number 81 82 real, intent(in) :: x 83 integer :: idigits 84 85 idigits = 1 86 ! If x /= 0 then: 87 if (abs(x) > 1.e-10) idigits = int(log10(abs(x))) + 1 88 89 END FUNCTION nb_digits 90 62 91 END MODULE info_PEM_mod -
trunk/LMDZ.COMMON/libf/evolution/pem.F90
r3498 r3512 941 941 enddo 942 942 deallocate(porefill) 943 call compute_massh2o_exchange_ssi(ngrid,nslope,nsoilmx_PEM,icetable_thickness_prev_iter,icetable_thickness,icetable_depth,tsurf_avg, tsoil_PEM,delta_h2o_icetablesublim) ! Mass of H2O exchange between the ssi and the atmosphere943 !call compute_massh2o_exchange_ssi(ngrid,nslope,nsoilmx_PEM,icetable_thickness_prev_iter,icetable_thickness,icetable_depth,tsurf_avg, tsoil_PEM,delta_h2o_icetablesublim) ! Mass of H2O exchange between the ssi and the atmosphere 944 944 endif 945 945 … … 949 949 ! II_d.5 Update the mass of the regolith adsorbed 950 950 if (adsorption_pem) then 951 call regolith_adsorption(ngrid,nslope,nsoilmx_PEM,timelen,d_h2oice,d_co2ice, &951 call regolith_adsorption(ngrid,nslope,nsoilmx_PEM,timelen,d_h2oice,d_co2ice, & 952 952 h2o_ice,co2_ice,tsoil_PEM,TI_PEM,ps_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, & 953 953 h2o_adsorbded_phys,delta_h2o_adsorbded,co2_adsorbded_phys,delta_co2_adsorbded) -
trunk/LMDZ.COMMON/libf/evolution/pemetat0.F90
r3498 r3512 326 326 write(*,*)'PEM settings: failed loading <ice_table_depth>' 327 327 write(*,*)'will reconstruct the values of the ice table given the current state' 328 call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_avg,watersoil_avg, TI_PEM(:,1,:),ice_table_depth,ice_table_thickness)328 ice_table_depth = -9999. 329 329 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM) 330 330 do islope = 1,nslope … … 335 335 if (.not. found) then 336 336 write(*,*)'PEM settings: failed loading <ice_porefilling>' 337 ice_porefilling = 0.337 ice_porefilling = 1. 338 338 endif 339 339 write(*,*) 'PEMETAT0: ICE TABLE done' … … 510 510 write(*,*) 'PEMETAT0: Ice table done' 511 511 else if (icetable_dynamic) then 512 ice_porefilling = 0.513 ice_table_depth = 0.512 ice_porefilling = 1. 513 ice_table_depth = -9999. 514 514 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM) 515 515 do islope = 1,nslope -
trunk/LMDZ.COMMON/libf/evolution/writediagpem.F90
r3498 r3512 51 51 use mod_phys_lmdz_para, only: is_parallel, is_mpi_root, is_master, gather 52 52 use mod_grid_phy_lmdz, only: klon_glo, Grid1Dto2D_glo, nbp_lon, nbp_lat, nbp_lev, grid_type, unstructured 53 use time_evol_mod, only: ecritpem , dt53 use time_evol_mod, only: ecritpem 54 54 55 55 implicit none … … 600 600 use mod_grid_phy_lmdz, only: klon_glo, Grid1Dto2D_glo, nbp_lon, nbp_lat 601 601 use mod_grid_phy_lmdz, only: grid_type, unstructured 602 use time_evol_mod, only: ecritpem , dt602 use time_evol_mod, only: ecritpem 603 603 use iniwritesoil_mod, only: iniwritesoil 604 604 … … 747 747 if (name.eq.firstname) then 748 748 ! if we run across 'firstname', then it is a new time step 749 zitau = zitau + dt749 zitau = zitau + 1 750 750 endif 751 751
Note: See TracChangeset
for help on using the changeset viewer.