Changeset 3319 for trunk/LMDZ.COMMON


Ignore:
Timestamp:
Apr 26, 2024, 5:03:35 PM (7 months ago)
Author:
jbclement
Message:

PEM:
Small correction about the dimension of an array.
JBC

Location:
trunk/LMDZ.COMMON/libf/evolution
Files:
8 edited

Legend:

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

    r3256 r3319  
    2929use glaciers_mod,          only: h2oice_flow, co2ice_flow, inf_h2oice_threshold, metam_co2ice_threshold, metam_h2oice_threshold, metam_h2oice, metam_co2ice
    3030use ice_table_mod,         only: icetable_equilibrium, icetable_dynamic
     31use layering_mod,          only: layering_algo
    3132
    3233implicit none
     
    103104write(*,*)  'Thermal properties of the regolith vary with pressure ?', reg_thprop_dependp
    104105
    105 !#---------- Layering parameters ----------#
    106106fluxgeo = 0.
    107107call getin('fluxgeo',fluxgeo)
     
    174174call getin('co2ice_flow',co2ice_flow)
    175175
     176!#---------- Layering parameters ----------#
     177layering_algo = .false.
     178call getin('layering',layering_algo)
     179
    176180END SUBROUTINE conf_pem
    177181
  • trunk/LMDZ.COMMON/libf/evolution/deftank/launch_pem.sh

    r3317 r3319  
    1818fi
    1919
     20# Save the current value of LC_NUMERIC and set it to a locale that uses a dot as the decimal separator
     21OLD_LC_NUMERIC=$LC_NUMERIC
     22LC_NUMERIC=en_US.UTF-8
     23
     24
     25#####################################################################
    2026# A few parameters that might need be changed depending on your setup:
    2127# Path to the arch.env to source:
    2228source ../trunk/LMDZ.COMMON/arch.env
    2329
    24 # Save the current value of LC_NUMERIC and set it to a locale that uses a dot as the decimal separator
    25 OLD_LC_NUMERIC=$LC_NUMERIC
    26 LC_NUMERIC=en_US.UTF-8
    27 
    28 
    29 #####################################################################
    3030#---------- Modify here the number of years to be simulated ------------
    3131## set the number of years, either Martian or Earth years:
  • trunk/LMDZ.COMMON/libf/evolution/deftank/run_PEM.def

    r3308 r3319  
    5252# reg_thprop_dependp=.false.
    5353
    54 #---------- Layering parameters ----------#
    5554# Value of the geothermal flux? Default = 0.
    5655# fluxgeo=0.
     
    9392# co2ice_flow=.true.
    9493
     94!#---------- Layering parameters ----------#
     95# Do you want to run with the layering algorithm? Default = .false.
     96# layering=.true.
     97
    9598# Some definitions for the physics, in file 'callphys.def'
    9699INCLUDEDEF=callphys.def
  • trunk/LMDZ.COMMON/libf/evolution/evol_ice_mod.F90

    r3308 r3319  
    106106    enddo
    107107
     108    new_tendencies = 0.
    108109    if (abs(pos_tend) < 1.e-10 .or. abs(neg_tend) < 1.e-10) then
    109110        write(*,*) "Reason of stopping: there is no sublimating or condensing h2o ice!"
     
    112113        write(*,*) "This can be due to the absence of h2o ice in the PCM run!"
    113114        stopPEM = 2
    114         new_tendencies = 0.
    115115    else
    116116        ! We adapt the tendencies to conserve h2o and do only exchange between grid points
  • trunk/LMDZ.COMMON/libf/evolution/layering_mod.F90

    r3317 r3319  
    1515real, parameter :: eps = epsilon(1.), tol = 1.e2*eps
    1616integer         :: nb_str_max
     17logical         :: layering_algo
    1718
    1819! Physical parameters
  • trunk/LMDZ.COMMON/libf/evolution/pem.F90

    r3317 r3319  
    7070use writediagpem_mod,           only: writediagpem, writediagsoilpem
    7171use co2condens_mod,             only: CO2cond_ps
    72 use layering_mod,               only: tend_dust, ptrarray, stratum, layering, ini_layering, del_layering, make_layering, get_nb_str_max, nb_str_max
     72use layering_mod,               only: tend_dust, ptrarray, stratum, layering, ini_layering, del_layering, make_layering, get_nb_str_max, nb_str_max, layering_algo
    7373
    7474#ifndef CPP_STD
     
    351351    status = nf90_close(ncid)
    352352
    353     call iniphysiq('startfi.nc',iim,jjm,llm,(jjm-1)*iim+2,comm_lmdz,daysec,day_ini,dtphys/nsplit_phys,rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp,iflag_phys)
     353    call iniphysiq(iim,jjm,llm,(jjm-1)*iim+2,comm_lmdz,daysec,day_ini,dtphys/nsplit_phys,rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp,iflag_phys)
    354354#else
    355355    ps_start_PCM(1) = ps(1)
     
    589589
    590590allocate(stratif(ngrid,nslope))
    591 do islope = 1,nslope
    592     do i = 1,ngrid
    593         call ini_layering(stratif(i,islope))
    594     enddo
    595 enddo
     591if (layering_algo) then
     592    do islope = 1,nslope
     593        do i = 1,ngrid
     594            call ini_layering(stratif(i,islope))
     595        enddo
     596    enddo
     597endif
    596598
    597599call pemetat0("startpem.nc",ngrid,nsoilmx,nsoilmx_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,porefillingice_depth, &
     
    655657year_iter = 0
    656658stopPEM = 0
    657 allocate(new_str(ngrid,nslope),new_lag1(ngrid,nslope),new_lag2(ngrid,nslope),current1(ngrid,nslope),current2(ngrid,nslope))
    658 new_str = .true.
    659 new_lag1 = .true.
    660 new_lag2 = .true.
    661 do islope = 1,nslope
    662     do ig = 1,ngrid
    663         current1(ig,islope)%p => stratif(ig,islope)%top
    664         current2(ig,islope)%p => stratif(ig,islope)%top
    665     enddo
    666 enddo
     659if (layering_algo) then
     660    allocate(new_str(ngrid,nslope),new_lag1(ngrid,nslope),new_lag2(ngrid,nslope),current1(ngrid,nslope),current2(ngrid,nslope))
     661    new_str = .true.
     662    new_lag1 = .true.
     663    new_lag2 = .true.
     664    do islope = 1,nslope
     665        do ig = 1,ngrid
     666            current1(ig,islope)%p => stratif(ig,islope)%top
     667            current2(ig,islope)%p => stratif(ig,islope)%top
     668        enddo
     669    enddo
     670endif
    667671
    668672do while (year_iter < 10 .and. i_myear < n_myear)
     
    748752    call evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbded,delta_h2o_icetablesublim,h2o_ice,tend_h2o_ice,stopPEM)
    749753    call evol_co2_ice(ngrid,nslope,co2_ice,tend_co2_ice)
    750     do islope = 1,nslope
    751         do ig = 1,ngrid
    752             call make_layering(stratif(ig,islope),tend_co2_ice(ig,islope),tend_h2o_ice(ig,islope),tend_dust,new_str(ig,islope),new_lag1(ig,islope),new_lag2(ig,islope),stopPEM,current1(ig,islope)%p,current2(ig,islope)%p)
    753         enddo
    754     enddo
     754    if (layering_algo) then
     755        do islope = 1,nslope
     756            do ig = 1,ngrid
     757                call make_layering(stratif(ig,islope),tend_co2_ice(ig,islope),tend_h2o_ice(ig,islope),tend_dust,new_str(ig,islope),new_lag1(ig,islope),new_lag2(ig,islope),stopPEM,current1(ig,islope)%p,current2(ig,islope)%p)
     758            enddo
     759        enddo
     760    endif
    755761
    756762!------------------------
     
    11221128!    III_c Write the "restartpem.nc"
    11231129!------------------------
    1124 nb_str_max = get_nb_str_max(stratif,ngrid,nslope) ! Get the maximum number of "stratum" in the stratification (layerings)
     1130if (layering_algo) nb_str_max = get_nb_str_max(stratif,ngrid,nslope) ! Get the maximum number of "stratum" in the stratification (layerings)
    11251131call pemdem0("restartpem.nc",longitude,latitude,cell_area,ngrid,nslope,def_slope,subslope_dist)
    11261132call pemdem1("restartpem.nc",i_myear,nsoilmx_PEM,ngrid,nslope,tsoil_PEM, &
     
    11361142write(*,*) "LL & RV & JBC: so far, so good!"
    11371143
    1138 do islope = 1,nslope
    1139     do i = 1,ngrid
    1140         call del_layering(stratif(i,islope))
    1141     enddo
    1142 enddo
    1143 deallocate(stratif,new_str,new_lag1,new_lag2,current1,current2)
     1144if (layering_algo) then
     1145    do islope = 1,nslope
     1146        do i = 1,ngrid
     1147            call del_layering(stratif(i,islope))
     1148        enddo
     1149    enddo
     1150    deallocate(new_str,new_lag1,new_lag2,current1,current2)
     1151endif
    11441152deallocate(vmr_co2_PCM,ps_timeseries,tsurf_PCM_timeseries,q_co2_PEM_phys,q_h2o_PEM_phys)
    11451153deallocate(co2_ice_PCM,watersurf_density_ave,watersoil_density_timeseries,Tsurfavg_before_saved)
    11461154deallocate(tsoil_phys_PEM_timeseries,watersoil_density_PEM_timeseries,watersoil_density_PEM_ave)
    11471155deallocate(delta_co2_adsorbded,delta_h2o_adsorbded,vmr_co2_PEM_phys,delta_h2o_icetablesublim,porefillingice_thickness_prev_iter)
    1148 deallocate(co2_ice_ini)
     1156deallocate(co2_ice_ini,stratif)
    11491157!----------------------------- END OUTPUT ------------------------------
    11501158
  • trunk/LMDZ.COMMON/libf/evolution/pemetat0.F90

    r3308 r3319  
    2323use compute_soiltemp_mod,       only: ini_tsoil_pem, compute_tsoil_pem
    2424use comslope_mod,               only: def_slope_mean, subslope_dist
    25 use layering_mod,               only: layering, array2stratif
     25use layering_mod,               only: layering, array2stratif, nb_str_max, layering_algo
    2626
    2727#ifndef CPP_STD
     
    7878logical                                 :: startpem_file                   ! boolean to check if we read the startfile or not
    7979real, dimension(:,:,:,:), allocatable   :: stratif_array                   ! Array for stratification (layerings)
    80 real                                    :: nb_str_max
    8180
    8281#ifdef CPP_STD
     
    118117!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    119118    ! Stratification (layerings)
    120     found = inquire_dimension("nb_str_max")
    121     if (.not. found) then
    122         write(*,*) 'Pemetat0: failed loading <nb_str_max>!'
    123         write(*,*) '''nb_str_max'' is set to 10!'
    124         nb_str_max = 10.
    125     else
    126         nb_str_max = inquire_dimension_length('nb_str_max')
     119    nb_str_max = 3
     120    if (layering_algo) then
     121        found = inquire_dimension("nb_str_max")
     122        if (.not. found) then
     123            write(*,*) 'Pemetat0: failed loading <nb_str_max>!'
     124            write(*,*) '''nb_str_max'' is set to 3!'
     125        else
     126            nb_str_max = int(inquire_dimension_length('nb_str_max'))
     127        endif
     128        allocate(stratif_array(ngrid,nslope,nb_str_max,6))
     129        stratif_array = 0.
     130        do islope = 1,nslope
     131            write(num,'(i2.2)') islope
     132            call get_field('stratif_slope'//num//'_thickness',stratif_array(:,islope,:,1),found)
     133            call get_field('stratif_slope'//num//'_top_elevation',stratif_array(:,islope,:,2),found2)
     134            found = found .or. found2
     135            call get_field('stratif_slope'//num//'_co2ice_volfrac',stratif_array(:,islope,:,3),found2)
     136            found = found .or. found2
     137            call get_field('stratif_slope'//num//'_h2oice_volfrac',stratif_array(:,islope,:,4),found2)
     138            found = found .or. found2
     139            call get_field('stratif_slope'//num//'_dust_volfrac',stratif_array(:,islope,:,5),found2)
     140            found = found .or. found2
     141            call get_field('stratif_slope'//num//'_air_volfrac',stratif_array(:,islope,:,6),found2)
     142            found = found .or. found2
     143            if (.not. found) then
     144                write(*,*) 'Pemetat0: failed loading at least one of the properties of <stratif_slope'//num//'>'
     145            endif ! not found
     146        enddo ! islope
     147        call array2stratif(stratif_array,ngrid,nslope,stratif)
     148        deallocate(stratif_array)
    127149    endif
    128     allocate(stratif_array(ngrid,nslope,int(nb_str_max),6))
    129     stratif_array = 0.
    130     do islope = 1,nslope
    131         write(num,'(i2.2)') islope
    132         call get_field('stratif_slope'//num//'_thickness',stratif_array(:,islope,:,1),found)
    133         call get_field('stratif_slope'//num//'_top_elevation',stratif_array(:,islope,:,2),found2)
    134         found = found .or. found2
    135         call get_field('stratif_slope'//num//'_co2ice_volfrac',stratif_array(:,islope,:,3),found2)
    136         found = found .or. found2
    137         call get_field('stratif_slope'//num//'_h2oice_volfrac',stratif_array(:,islope,:,4),found2)
    138         found = found .or. found2
    139         call get_field('stratif_slope'//num//'_dust_volfrac',stratif_array(:,islope,:,5),found2)
    140         found = found .or. found2
    141         call get_field('stratif_slope'//num//'_air_volfrac',stratif_array(:,islope,:,6),found2)
    142         found = found .or. found2
    143         if (.not. found) then
    144             write(*,*) 'Pemetat0: failed loading at least one of the properties of <stratif_slope'//num//'>'
    145         endif ! not found
    146     enddo ! islope
    147     call array2stratif(stratif_array,ngrid,nslope,stratif)
    148     deallocate(stratif_array)
    149150
    150151!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    358359
    359360    ! Stratification (layerings)
    360     write(*,*)'So the stratification (layerings) is initialized with only the 3 sub-surface strata.'
    361361    nb_str_max = 3
     362    if (layering_algo) write(*,*)'So the stratification (layerings) is initialized with only the 3 sub-surface strata.'
    362363
    363364    ! h2o ice
  • trunk/LMDZ.COMMON/libf/evolution/pemredem.F90

    r3313 r3319  
    6464use comsoil_h_PEM, only: inertiedat_PEM, soil_pem
    6565use time_evol_mod, only: year_bp_ini, convert_years
    66 use layering_mod,  only: layering, nb_str_max, stratif2array, print_layering
     66use layering_mod,  only: layering, nb_str_max, stratif2array, print_layering, layering_algo
    6767
    6868implicit none
     
    9696call put_field('h2o_ice','h2o_ice',h2o_ice,Year)
    9797
    98 allocate(stratif_array(ngrid,nslope,nb_str_max,6))
    99 call stratif2array(stratif,ngrid,nslope,stratif_array)
    100 do islope = 1,nslope
    101     write(num,fmt='(i2.2)') islope
    102     call put_field('stratif_slope'//num//'_thickness','Layering thickness',stratif_array(:,islope,:,1),Year)
    103     call put_field('stratif_slope'//num//'_top_elevation','Layering top elevation',stratif_array(:,islope,:,2),Year)
    104     call put_field('stratif_slope'//num//'_co2ice_volfrac','Layering CO2 ice volume fraction',stratif_array(:,islope,:,3),Year)
    105     call put_field('stratif_slope'//num//'_h2oice_volfrac','Layering H2O ice volume fraction',stratif_array(:,islope,:,4),Year)
    106     call put_field('stratif_slope'//num//'_dust_volfrac','Layering dust volume fraction',stratif_array(:,islope,:,5),Year)
    107     call put_field('stratif_slope'//num//'_air_volfrac','Layering air volume fraction',stratif_array(:,islope,:,6),Year)
    108 enddo
    109 deallocate(stratif_array)
     98if (layering_algo) then
     99    allocate(stratif_array(ngrid,nslope,nb_str_max,6))
     100    call stratif2array(stratif,ngrid,nslope,stratif_array)
     101    do islope = 1,nslope
     102        write(num,fmt='(i2.2)') islope
     103        call put_field('stratif_slope'//num//'_thickness','Layering thickness',stratif_array(:,islope,:,1),Year)
     104        call put_field('stratif_slope'//num//'_top_elevation','Layering top elevation',stratif_array(:,islope,:,2),Year)
     105        call put_field('stratif_slope'//num//'_co2ice_volfrac','Layering CO2 ice volume fraction',stratif_array(:,islope,:,3),Year)
     106        call put_field('stratif_slope'//num//'_h2oice_volfrac','Layering H2O ice volume fraction',stratif_array(:,islope,:,4),Year)
     107        call put_field('stratif_slope'//num//'_dust_volfrac','Layering dust volume fraction',stratif_array(:,islope,:,5),Year)
     108        call put_field('stratif_slope'//num//'_air_volfrac','Layering air volume fraction',stratif_array(:,islope,:,6),Year)
     109    enddo
     110    deallocate(stratif_array)
     111endif
    110112
    111113if (soil_pem) then
Note: See TracChangeset for help on using the changeset viewer.