Ignore:
Timestamp:
Dec 6, 2024, 5:47:19 PM (2 weeks ago)
Author:
jbclement
Message:

PEM:
Small fixes to initialize and output ice table-related variables and in the launching script.
JBC

File:
1 edited

Legend:

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

    r3532 r3537  
    77!=======================================================================
    88
    9 SUBROUTINE pemetat0(filename,ngrid,nsoil_PCM,nsoil_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,ice_table_depth,ice_table_thickness, &
     9SUBROUTINE pemetat0(filename,ngrid,nsoil_PCM,nsoil_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,icetable_depth,icetable_thickness, &
    1010                    ice_porefilling,tsurf_avg_yr1,tsurf_avg_yr2,q_co2,q_h2o,ps_inst,tsoil_inst,d_h2oice,d_co2ice,co2_ice,h2o_ice,    &
    1111                    global_avg_pressure,watersurf_avg,watersoil_avg,m_co2_regolith_phys,deltam_co2_regolith_phys,                    &
     
    1616use comsoil_h,                  only: volcapa, inertiedat
    1717use adsorption_mod,             only: regolith_adsorption, adsorption_pem
    18 use ice_table_mod,              only: computeice_table_equilibrium, icetable_depth, icetable_thickness, icetable_equilibrium, icetable_dynamic
     18use ice_table_mod,              only: computeice_table_equilibrium, icetable_equilibrium, icetable_dynamic
    1919use constants_marspem_mod,      only: alpha_clap_h2o, beta_clap_h2o, TI_breccia, TI_bedrock
    2020use soil_thermalproperties_mod, only: update_soil_thermalproperties
     
    6060real, dimension(ngrid,nsoil_PEM,nslope),         intent(inout) :: TI_PEM              ! soil (mid-layer) thermal inertia in the PEM grid [SI]
    6161real, dimension(ngrid,nsoil_PEM,nslope),         intent(inout) :: tsoil_PEM           ! soil (mid-layer) temperature [K]
    62 real, dimension(ngrid,nslope),                   intent(inout) :: ice_table_depth     ! Ice table depth [m]
    63 real, dimension(ngrid,nslope),                   intent(inout) :: ice_table_thickness ! Ice table thickness [m]
     62real, dimension(ngrid,nslope),                   intent(inout) :: icetable_depth      ! Ice table depth [m]
     63real, dimension(ngrid,nslope),                   intent(inout) :: icetable_thickness ! Ice table thickness [m]
    6464real, dimension(ngrid,nsoil_PEM,nslope),         intent(inout) :: ice_porefilling     ! Subsurface ice pore filling [m3/m3]
    6565real, dimension(ngrid,nsoil_PEM,nslope,timelen), intent(inout) :: tsoil_inst          ! instantaneous soil (mid-layer) temperature [K]
     
    108108
    109109!0.2 Set to default values
    110 ice_table_depth = -1. ! by default, no ice table
    111 ice_table_thickness = -1.
     110icetable_depth = -1. ! by default, no ice table
     111icetable_thickness = -1.
     112ice_porefilling = 0.
    112113!1. Run
    113114if (startpem_file) then
     
    305306!3. Ice Table
    306307        if (icetable_equilibrium) then
    307             call get_field("ice_table_depth",ice_table_depth,found)
     308            call get_field("icetable_depth",icetable_depth,found)
    308309            if (.not. found) then
    309                 write(*,*)'PEM settings: failed loading <ice_table_depth>'
     310                write(*,*)'PEM settings: failed loading <icetable_depth>'
    310311                write(*,*)'will reconstruct the values of the ice table given the current state'
    311                 call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_avg,watersoil_avg,TI_PEM(:,1,:),ice_table_depth,ice_table_thickness)
    312                 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,ice_porefilling,icetable_equilibrium,icetable_dynamic,TI_PEM)
     312                call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_avg,watersoil_avg,TI_PEM(:,1,:),icetable_depth,icetable_thickness)
     313                call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,icetable_depth,icetable_thickness,ice_porefilling,icetable_equilibrium,icetable_dynamic,TI_PEM)
    313314                do islope = 1,nslope
    314315                    call ini_tsoil_pem(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope))
     
    318319        else if (icetable_dynamic) then
    319320            call get_field("ice_porefilling",ice_porefilling,found)
     321            if (.not. found) write(*,*)'PEM settings: failed loading <ice_porefilling>'
     322            call get_field("icetable_depth",icetable_depth,found)
    320323            if (.not. found) then
    321                 write(*,*)'PEM settings: failed loading <ice_porefilling>'
    322                 ice_porefilling = 0.
    323             endif
    324             call get_field("ice_table_depth",ice_table_depth,found)
    325             if (.not. found) then
    326                 write(*,*)'PEM settings: failed loading <ice_table_depth>'
     324                write(*,*)'PEM settings: failed loading <icetable_depth>'
    327325                write(*,*)'will reconstruct the values of the ice table given the current state'
    328                 ice_table_depth = -9999.
    329                 call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,ice_porefilling,icetable_equilibrium,icetable_dynamic,TI_PEM)
     326                call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,icetable_depth,icetable_thickness,ice_porefilling,icetable_equilibrium,icetable_dynamic,TI_PEM)
    330327                do islope = 1,nslope
    331328                    call ini_tsoil_pem(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope))
     
    498495!c) Ice table
    499496        if (icetable_equilibrium) then
    500             call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_avg,watersoil_avg,TI_PEM(:,1,:),ice_table_depth,ice_table_thickness)
    501             call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,ice_porefilling,icetable_equilibrium,icetable_dynamic,TI_PEM)
     497            call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_avg,watersoil_avg,TI_PEM(:,1,:),icetable_depth,icetable_thickness)
     498            call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,icetable_depth,icetable_thickness,ice_porefilling,icetable_equilibrium,icetable_dynamic,TI_PEM)
    502499            do islope = 1,nslope
    503500                call ini_tsoil_pem(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope))
     
    505502            write(*,*) 'PEMETAT0: Ice table done'
    506503        else if (icetable_dynamic) then
    507             ice_porefilling = 0.
    508             ice_table_depth = -9999.
    509             call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,ice_table_depth,ice_table_thickness,ice_porefilling,icetable_equilibrium,icetable_dynamic,TI_PEM)
     504            call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,d_h2oice,h2o_ice,global_avg_pressure,icetable_depth,icetable_thickness,ice_porefilling,icetable_equilibrium,icetable_dynamic,TI_PEM)
    510505            do islope = 1,nslope
    511506                call ini_tsoil_pem(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_avg_yr2(:,islope),tsoil_PEM(:,:,islope))
Note: See TracChangeset for help on using the changeset viewer.