Changeset 3512


Ignore:
Timestamp:
Nov 12, 2024, 6:35:33 PM (9 days ago)
Author:
jbclement
Message:

PEM:
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.
JBC

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  
    99!!!
    1010!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    11 
    12 
    1311
    1412SUBROUTINE dyn_ss_ice_m(ssi_depth_in,T1,Tb,nz,thIn,p0,pfrost,porefill_in,porefill,ssi_depth)
     
    6967  !call setgrid(nz,z,zmax,zfac)
    7068  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.)))
    7371  enddo
    7472 
  • trunk/LMDZ.COMMON/libf/evolution/NS_fast_subs_mars.F90

    r3493 r3512  
    116116     call icechanges(nz,z(:),typeF,avdrho(k),avdrhoP(k),ypp(:), &
    117117          & Diff,porosity,icefrac,bigstep,zdepthT(k),porefill(:,k),typeG)
    118 
     118     if (typeP>2) then
    119119     if (mode2 .and. porefill(typeP,k)>=1. .and. porefill(typeP-1,k)==0.) then  ! nothing changed
    120120        porefill(typeP-1,k)=1.  ! paste a layer
    121121   !     write(34,*) '# mode 2 growth occurred',typeP,typeF,typeT
     122     endif
    122123     endif
    123124
  • trunk/LMDZ.COMMON/libf/evolution/changelog.txt

    r3498 r3512  
    477477- Renaming of the tendencies in the PEM with the prefix 'd_' instead of 'tend_';
    478478- 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
     481Few 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  
    2828
    2929allocate(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
     30allocate(icetable_thickness(ngrid,nslope))
     31allocate(ice_porefilling(ngrid,nsoil,nslope))
    3532
    3633END SUBROUTINE ini_ice_table
  • trunk/LMDZ.COMMON/libf/evolution/info_PEM_mod.F90

    r3498 r3512  
    3131logical       :: ok
    3232integer       :: cstat
    33 character(10) :: ich1, ich2, ich3, ich4, ich5, ich6, fch
     33character(10) :: frmt
     34character(20) :: ich1, ich2, ich3, ich4, fch1, fch2, fch3
    3435
    3536!----- Code
    3637inquire(file = 'info_PEM.txt',exist = ok)
    3738if (ok) then
    38     write(ich1,'(f0.4)') i_myear
    39     write(ich2,'(f0.4)') n_myear
    40     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(ich3,'(i0)') iPCM
    42     write(ich4,'(i0)') iPEM + 1
    43     write(ich5,'(i0)') nPCM
    44     write(ich6,'(i0)') nPCM_ini
    45     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)
    4647    if (cstat > 0) then
    4748        error stop 'info_PEM: command execution failed!'
     
    6061END SUBROUTINE info_PEM
    6162
     63!=======================================================================
     64
     65FUNCTION int2str(i) RESULT(str)
     66! Function to convert an integer into a string
     67
     68integer, intent(in) :: i
     69character(20)       :: str
     70
     71if (nb_digits(real(i)) > len(str)) error stop 'int2str [info_PEM_mod]: invalid integer for conversion!'
     72write(str,'(i0)') i
     73str = trim(adjustl(str))
     74
     75END FUNCTION int2str
     76
     77!=======================================================================
     78
     79FUNCTION nb_digits(x) RESULT(idigits)
     80! Function to give the number of digits for the integer part of a real number
     81
     82real, intent(in) :: x
     83integer          :: idigits
     84
     85idigits = 1
     86! If x /= 0 then:
     87if (abs(x) > 1.e-10) idigits = int(log10(abs(x))) + 1
     88
     89END FUNCTION nb_digits
     90
    6291END MODULE info_PEM_mod
  • trunk/LMDZ.COMMON/libf/evolution/pem.F90

    r3498 r3512  
    941941            enddo
    942942            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 atmosphere
     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 atmosphere
    944944        endif
    945945
     
    949949! II_d.5 Update the mass of the regolith adsorbed
    950950        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,                           &
    952952                                     h2o_ice,co2_ice,tsoil_PEM,TI_PEM,ps_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys, &
    953953                                     h2o_adsorbded_phys,delta_h2o_adsorbded,co2_adsorbded_phys,delta_co2_adsorbded)
  • trunk/LMDZ.COMMON/libf/evolution/pemetat0.F90

    r3498 r3512  
    326326                write(*,*)'PEM settings: failed loading <ice_table_depth>'
    327327                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.
    329329                call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM)
    330330                do islope = 1,nslope
     
    335335            if (.not. found) then
    336336                write(*,*)'PEM settings: failed loading <ice_porefilling>'
    337                 ice_porefilling = 0.
     337                ice_porefilling = 1.
    338338            endif
    339339            write(*,*) 'PEMETAT0: ICE TABLE done'
     
    510510            write(*,*) 'PEMETAT0: Ice table done'
    511511        else if (icetable_dynamic) then
    512             ice_porefilling = 0.
    513             ice_table_depth = 0.
     512            ice_porefilling = 1.
     513            ice_table_depth = -9999.
    514514            call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,TI_PEM)
    515515            do islope = 1,nslope
  • trunk/LMDZ.COMMON/libf/evolution/writediagpem.F90

    r3498 r3512  
    5151use mod_phys_lmdz_para, only: is_parallel, is_mpi_root, is_master, gather
    5252use 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, dt
     53use time_evol_mod,      only: ecritpem
    5454
    5555implicit none
     
    600600use mod_grid_phy_lmdz,  only: klon_glo, Grid1Dto2D_glo, nbp_lon, nbp_lat
    601601use mod_grid_phy_lmdz,  only: grid_type, unstructured
    602 use time_evol_mod,      only: ecritpem, dt
     602use time_evol_mod,      only: ecritpem
    603603use iniwritesoil_mod,   only: iniwritesoil
    604604
     
    747747if (name.eq.firstname) then
    748748  ! if we run across 'firstname', then it is a new time step
    749   zitau = zitau + dt
     749  zitau = zitau + 1
    750750endif
    751751
Note: See TracChangeset for help on using the changeset viewer.