source: trunk/LMDZ.COMMON/libf/evolution/pemetat0.F90 @ 3129

Last change on this file since 3129 was 3123, checked in by llange, 2 years ago

MARS PEM
1) Adapting the Mars PEM soil grid to the one of the PCM. The first layers in the PEM follow those from the PCM (PYM grid), and then, for layers at depth, we use the classical power low grid.
2) Correction when reading the soil temperature, water density at the surface, and initialization of the ice table.
LL

File size: 22.5 KB
RevLine 
[3076]1MODULE pemetat0_mod
[3019]2
[3076]3implicit none
4
5!=======================================================================
6contains
7!=======================================================================
8
9SUBROUTINE pemetat0(filename,ngrid,nsoil_GCM,nsoil_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,ice_table, ice_table_thickness,   &
10                    tsurf_ave_yr1,tsurf_ave_yr2,q_co2,q_h2o,ps_inst,tsoil_inst,tend_h2oglaciers,tend_co2glaciers,co2ice,waterice, &
11                    global_ave_pressure,watersurf_ave,watersoil_ave, m_co2_regolith_phys,deltam_co2_regolith_phys,                &
12                    m_h2o_regolith_phys,deltam_h2o_regolith_phys, water_reservoir)
13
14use iostart_PEM,                only: open_startphy, close_startphy, get_field, get_var
15use comsoil_h_PEM,              only: soil_pem, layer_PEM, mlayer_PEM, fluxgeo, inertiedat_PEM, water_reservoir_nom, depth_breccia, depth_bedrock, index_breccia, index_bedrock
16use comsoil_h,                  only: volcapa,inertiedat
17use adsorption_mod,             only: regolith_adsorption, adsorption_pem
18use ice_table_mod,              only: computeice_table_equilibrium
19use constants_marspem_mod,      only: alpha_clap_h2o, beta_clap_h2o, TI_breccia, TI_bedrock
20use soil_thermalproperties_mod, only: update_soil_thermalproperties
21use tracer_mod,                 only: mmol, igcm_h2o_vap ! tracer names and molar masses
22use abort_pem_mod,              only: abort_pem
23use soil_pem_compute_mod,       only: soil_pem_compute
24use soil_pem_ini_mod,           only: soil_pem_ini
25
[3019]26#ifndef CPP_STD
[3039]27    use comcstfi_h,   only: r, mugaz
28    use surfdat_h,    only: watercaptag
[3019]29#else
[3039]30    use comcstfi_mod, only: r, mugaz
[3019]31#endif
32
[3076]33implicit none
[3019]34
[3076]35include "callkeys.h"
[2835]36
[3076]37character(len=*),               intent(in) :: filename            ! name of the startfi_PEM.nc
38integer,                        intent(in) :: ngrid               ! # of physical grid points
39integer,                        intent(in) :: nsoil_GCM           ! # of vertical grid points in the GCM
40integer,                        intent(in) :: nsoil_PEM           ! # of vertical grid points in the PEM
41integer,                        intent(in) :: nslope              ! # of sub-grid slopes
42integer,                        intent(in) :: timelen             ! # time samples
43real,                           intent(in) :: timestep            ! time step [s]
44real,                           intent(in) :: global_ave_pressure ! mean average pressure on the planet [Pa]
45real, dimension(ngrid,nslope),  intent(in) :: tsurf_ave_yr1       ! surface temperature at the first year of GCM call [K]
46real, dimension(ngrid,nslope),  intent(in) :: tsurf_ave_yr2       ! surface temperature at the second  year of GCM call [K]
47real, dimension(ngrid,timelen), intent(in) :: q_co2               ! MMR tracer co2 [kg/kg]
48real, dimension(ngrid,timelen), intent(in) :: q_h2o               ! MMR tracer h2o [kg/kg]
49real, dimension(ngrid,timelen), intent(in) :: ps_inst             ! surface pressure [Pa]
50real, dimension(ngrid,nslope),  intent(in) :: tend_h2oglaciers    ! tendencies on h2o glaciers
51real, dimension(ngrid,nslope),  intent(in) :: tend_co2glaciers    ! tendencies on co2 glaciers
52real, dimension(ngrid,nslope),  intent(in) :: co2ice              ! co2 ice amount [kg/m^2]
53real, dimension(ngrid,nslope),  intent(in) :: waterice            ! water ice amount [kg/m^2]
54real, dimension(ngrid,nslope),  intent(in) :: watersurf_ave       ! surface water ice density, yearly averaged  (kg/m^3)
[2794]55! outputs
[3076]56real, dimension(ngrid),                          intent(out) :: deltam_co2_regolith_phys ! mass of co2 that is exchanged due to adsorption desorption [kg/m^2]
57real, dimension(ngrid),                          intent(out) :: deltam_h2o_regolith_phys ! mass of h2o that is exchanged due to adsorption desorption [kg/m^2]
58real, dimension(ngrid,nsoil_PEM,nslope),         intent(inout) :: TI_PEM              ! soil (mid-layer) thermal inertia in the PEM grid [SI]
59real, dimension(ngrid,nsoil_PEM,nslope),         intent(inout) :: tsoil_PEM           ! soil (mid-layer) temperature [K]
60real, dimension(ngrid,nslope),                   intent(inout) :: ice_table           ! Ice table depth [m]
61real, dimension(ngrid,nslope),                   intent(inout) :: ice_table_thickness ! Ice table thickness [m]
62real, dimension(ngrid,nsoil_PEM,nslope,timelen), intent(inout) :: tsoil_inst          ! instantaneous soil (mid-layer) temperature [K]
63real, dimension(ngrid,nsoil_PEM,nslope),         intent(inout) :: m_co2_regolith_phys ! mass of co2 adsorbed [kg/m^2]
64real, dimension(ngrid,nsoil_PEM,nslope),         intent(inout) :: m_h2o_regolith_phys ! mass of h2o adsorbed [kg/m^2]
65real, dimension(ngrid),                          intent(inout) :: water_reservoir     ! mass of h2o that is exchanged due to adsorption desorption [kg/m^2]
66real, dimension(ngrid,nsoil_PEM,nslope),         intent(inout) :: watersoil_ave       ! surface water ice density, yearly averaged (kg/m^3)
[2794]67! local
[3076]68real, dimension(ngrid,nsoil_PEM,nslope) :: tsoil_startPEM               ! soil temperature saved in the start [K]
69real, dimension(ngrid,nsoil_PEM,nslope) :: TI_startPEM                  ! soil thermal inertia saved in the start [SI]
70logical                                 :: found                        ! check if variables are found in the start
71logical                                 :: found2                       ! check if variables are found in the start
72integer                                 :: iloop, ig, islope, it, isoil ! index for loops
73real                                    :: kcond                        ! Thermal conductivity, intermediate variable [SI]
74real                                    :: delta                        ! Depth of the interface regolith-breccia, breccia -bedrock [m]
75character(2)                            :: num                          ! intermediate string to read PEM start sloped variables
76real, dimension(ngrid,nsoil_PEM)        :: tsoil_saved                  ! saved soil temperature [K]
77real, dimension(ngrid,nsoil_PEM,nslope) :: tsoil_tmp_yr1                ! intermediate soil temperature during yr1[K]
78real, dimension(ngrid,nsoil_PEM,nslope) :: tsoil_tmp_yr2                ! intermediate soil temperature during yr 2 [K]
79real, dimension(ngrid,nsoil_PEM - 1)    :: alph_tmp                     ! Intermediate for tsoil computation []
80real, dimension(ngrid,nsoil_PEM - 1)    :: beta_tmp                     ! Intermediate for tsoil computatio []
81logical                                 :: startpem_file                ! boolean to check if we read the startfile or not
[2835]82
[3076]83#ifdef CPP_STD
84   logical, dimension(ngrid) :: watercaptag
85   watercaptag(:) = .false.
[2985]86#endif
87
[2794]88!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
89!!!
90!!! Purpose: read start_pem. Need a specific iostart_PEM
91!!!
[2888]92!!! Order: 0. Previous year of the PEM run
[3076]93!!!        1. Thermal Inertia
[2888]94!!!        2. Soil Temperature
95!!!        3. Ice table
96!!!        4. Mass of CO2 & H2O adsorbed
97!!!        5. Water reservoir
[2794]98!!!
99!!! /!\ This order must be respected !
100!!! Author: LL
101!!!
102!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2779]103
[2863]104!0. Check if the start_PEM exist.
105
106inquire(file=filename,exist =  startpem_file)
107
[2888]108write(*,*)'Is start PEM?',startpem_file
[2863]109
[2794]110!1. Run
111if (startpem_file) then
[3076]112    ! open pem initial state file:
113    call open_startphy(filename)
[2835]114
[3039]115    if (soil_pem) then
[3076]116
[2794]117!1. Thermal Inertia
118! a. General case
[3076]119    do islope = 1,nslope
120        write(num,'(i2.2)') islope
121        call get_field("TI_PEM_slope"//num,TI_startPEM(:,:,islope),found)
122        if (.not. found) then
123            write(*,*)'PEM settings: failed loading <TI_PEM_slope'//num//'>'
124            write(*,*)'will reconstruct the values of TI_PEM'
[2779]125
[3076]126            do ig = 1,ngrid
127                if (TI_PEM(ig,index_breccia,islope) < TI_breccia) then
128                    !!! transition
129                    delta = depth_breccia
130                    TI_PEM(ig,index_breccia+1,islope) = sqrt((layer_PEM(index_breccia + 1) - layer_PEM(index_breccia))/ &
131                                                        (((delta - layer_PEM(index_breccia))/(TI_PEM(ig,index_breccia,islope)**2)) + &
132                                                        ((layer_PEM(index_breccia + 1) - delta)/(TI_breccia**2))))
133                    do iloop=index_breccia+2,index_bedrock
134                        TI_PEM(ig,iloop,islope) = TI_breccia
135                    enddo
136                else ! we keep the high ti values
137                    do iloop = index_breccia + 1,index_bedrock
138                        TI_PEM(ig,iloop,islope) = TI_PEM(ig,index_breccia,islope)
139                    enddo
140                endif ! TI PEM and breccia comparison
141                !! transition
142                delta = depth_bedrock
143                TI_PEM(ig,index_bedrock + 1,islope) = sqrt((layer_PEM(index_bedrock + 1) - layer_PEM(index_bedrock))/ &
144                                                        (((delta - layer_PEM(index_bedrock))/(TI_PEM(ig,index_bedrock,islope)**2)) + &
145                                                        ((layer_PEM(index_bedrock + 1) - delta)/(TI_bedrock**2))))
146                do iloop = index_bedrock + 2,nsoil_PEM
147                    TI_PEM(ig,iloop,islope) = TI_bedrock
148                enddo
149            enddo
150        else ! found
151            do iloop = nsoil_GCM + 1,nsoil_PEM
152                TI_PEM(:,iloop,islope) = TI_startPEM(:,iloop,islope)  ! ! 1st layers can change because of the presence of ice at the surface, so we don't change it here.
153            enddo
154        endif ! not found
155    enddo ! islope
[2779]156
[3082]157    write(*,*) 'PEMETAT0: THERMAL INERTIA done'
[2779]158
[2794]159! b. Special case for inertiedat, inertiedat_PEM
160call get_field("inertiedat_PEM",inertiedat_PEM,found)
161if(.not.found) then
162 do iloop = 1,nsoil_GCM
163   inertiedat_PEM(:,iloop) = inertiedat(:,iloop)
[3076]164 enddo
[2794]165!!! zone de transition
[2895]166delta = depth_breccia
[2794]167do ig = 1,ngrid
[3076]168if(inertiedat_PEM(ig,index_breccia).lt.TI_breccia) then
[2895]169inertiedat_PEM(ig,index_breccia+1) = sqrt((layer_PEM(index_breccia+1)-layer_PEM(index_breccia))/ &
170            (((delta-layer_PEM(index_breccia))/(inertiedat(ig,index_breccia)**2))+ &
171                      ((layer_PEM(index_breccia+1)-delta)/(TI_breccia**2))))
[2779]172
[3076]173 do iloop = index_breccia+2,index_bedrock
[2794]174       inertiedat_PEM(ig,iloop) = TI_breccia
175  enddo
[2779]176
[2794]177else
[2895]178   do iloop=index_breccia+1,index_bedrock
[2794]179      inertiedat_PEM(ig,iloop) = inertiedat_PEM(ig,nsoil_GCM)
[3076]180   enddo
[2794]181endif ! comparison ti breccia
182enddo!ig
[2779]183
[2794]184!!! zone de transition
[2895]185delta = depth_bedrock
[2794]186do ig = 1,ngrid
[2895]187inertiedat_PEM(ig,index_bedrock+1) = sqrt((layer_PEM(index_bedrock+1)-layer_PEM(index_bedrock))/ &
188            (((delta-layer_PEM(index_bedrock))/(inertiedat_PEM(ig,index_bedrock)**2))+ &
189                      ((layer_PEM(index_bedrock+1)-delta)/(TI_bedrock**2))))
[2794]190enddo
[2779]191
[2895]192 do iloop = index_bedrock+2, nsoil_PEM
[2794]193   do ig = 1,ngrid
194      inertiedat_PEM(ig,iloop) = TI_bedrock
195   enddo
196 enddo
197endif ! not found
198
[3076]199!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2794]200!2. Soil Temperature
[3076]201do islope=1,nslope
[2779]202  write(num,fmt='(i2.2)') islope
[2794]203   call get_field("tsoil_PEM_slope"//num,tsoil_startPEM(:,:,islope),found)
204  if(.not.found) then
205      write(*,*)'PEM settings: failed loading <tsoil_PEM_slope'//num//'>'
206      write(*,*)'will reconstruct the values of Tsoil'
[2895]207!      do ig = 1,ngrid
208!        kcond = (TI_PEM(ig,index_breccia+1,islope)*TI_PEM(ig,index_breccia+1,islope))/volcapa
[3076]209!        tsoil_PEM(ig,index_breccia+1,islope) = tsoil_PEM(ig,index_breccia,islope) + fluxgeo/kcond*(mlayer_PEM(index_breccia)-mlayer_PEM(index_breccia-1))
[2895]210!       do iloop=index_breccia+2,index_bedrock
211!            kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa
212!            tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_breccia+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_breccia))
213!      enddo
214!        kcond = (TI_PEM(ig,index_bedrock+1,islope)*TI_PEM(ig,index_bedrock+1,islope))/volcapa
[3076]215!        tsoil_PEM(ig,index_bedrock+1,islope) = tsoil_PEM(ig,index_bedrock,islope) + fluxgeo/kcond*(mlayer_PEM(index_bedrock)-mlayer_PEM(index_bedrock-1))
[2895]216!
217!      do iloop=index_bedrock+2,nsoil_PEM
218!            kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa
219!            tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_bedrock+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_bedrock))
220!      enddo
221!      enddo
[2794]222
223
[2895]224     call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope))
[3076]225     call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope))
[2895]226
[3076]227
[2794]228   else
229! predictor corrector: restart from year 1 of the GCM and build the evolution of
230! tsoil at depth
231
232    tsoil_tmp_yr1(:,:,islope) = tsoil_startPEM(:,:,islope)
[3076]233    call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_ave_yr1(:,islope),tsoil_tmp_yr1(:,:,islope))
234    call soil_pem_compute(ngrid,nsoil_PEM,.false.,TI_PEM(:,:,islope),timestep,tsurf_ave_yr1(:,islope),tsoil_tmp_yr1(:,:,islope))
235    tsoil_tmp_yr2(:,:,islope) = tsoil_tmp_yr1(:,:,islope)
236    call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_ave_yr2(:,islope),tsoil_tmp_yr2(:,:,islope))
[2794]237
238
239     do iloop = nsoil_GCM+1,nsoil_PEM
240       tsoil_PEM(:,iloop,islope) = tsoil_tmp_yr2(:,iloop,islope)
241     enddo
[2895]242   endif !found
[2794]243
244    do it = 1,timelen
245        do isoil = nsoil_GCM+1,nsoil_PEM
246        tsoil_inst(:,isoil,islope,it) = tsoil_PEM(:,isoil,islope)
247        enddo
248     enddo
[2849]249      do isoil = nsoil_GCM+1,nsoil_PEM
250        do ig = 1,ngrid
[3019]251        watersoil_ave(ig,isoil,islope) = exp(beta_clap_h2o/tsoil_PEM(ig,isoil,islope) + alpha_clap_h2o)/tsoil_PEM(ig,isoil,islope)*mmol(igcm_h2o_vap)/(mugaz*r)
[2849]252        enddo
253      enddo
[3076]254enddo ! islope
[2835]255
[3082]256write(*,*) 'PEMETAT0: SOIL TEMP done'
[2779]257
[3076]258!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2794]259!3. Ice Table
[2895]260  call get_field("ice_table",ice_table,found)
261   if(.not.found) then
262      write(*,*)'PEM settings: failed loading <ice_table>'
263      write(*,*)'will reconstruct the values of the ice table given the current state'
[3123]264      ice_table(:,:) = -1  ! by default, no ice table 
265      ice_table_thickness(:,:) = -1  ! by default, no ice table
[2961]266     call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_ave,watersoil_ave, TI_PEM(:,1,:),ice_table,ice_table_thickness)
267     call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,tend_h2oglaciers,waterice,global_ave_pressure,ice_table,ice_table_thickness,TI_PEM)
[2895]268     do islope = 1,nslope
269     call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope))
270     enddo
271   endif
[2794]272
[3082]273write(*,*) 'PEMETAT0: ICE TABLE done'
[2794]274
[3076]275!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2863]276!4. CO2 & H2O Adsorption
[2888]277 if(adsorption_pem) then
[3076]278  do islope=1,nslope
[2863]279   write(num,fmt='(i2.2)') islope
[2794]280   call get_field("mco2_reg_ads_slope"//num,m_co2_regolith_phys(:,:,islope),found)
[2863]281    if((.not.found)) then
282       m_co2_regolith_phys(:,:,:) = 0.
[2939]283       exit
[2863]284    endif
[2794]285
[3076]286  enddo
287
288  do islope=1,nslope
[2863]289   write(num,fmt='(i2.2)') islope
[2939]290   call get_field("mh2o_reg_ads_slope"//num,m_h2o_regolith_phys(:,:,islope),found2)
[2863]291    if((.not.found2)) then
292       m_h2o_regolith_phys(:,:,:) = 0.
[2939]293      exit
[2863]294    endif
[2849]295
[3076]296  enddo
297
[2863]298    call regolith_adsorption(ngrid,nslope,nsoil_PEM,timelen,tend_h2oglaciers,tend_co2glaciers,waterice,co2ice,tsoil_PEM,TI_PEM,ps_inst,q_co2,q_h2o, &
299                                m_h2o_regolith_phys,deltam_h2o_regolith_phys, m_co2_regolith_phys,deltam_co2_regolith_phys)
[2779]300
[2863]301    if((.not.found)) then
302      deltam_co2_regolith_phys(:) = 0.
303    endif
304    if((.not.found2)) then
[3076]305       deltam_h2o_regolith_phys(:) = 0.
[2863]306    endif
[3082]307write(*,*) 'PEMETAT0: CO2 & H2O adsorption done'
[2888]308    endif
[2835]309endif ! soil_pem
[2794]310
[3076]311!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2888]312!. 5 water reservoir
[3076]313#ifndef CPP_STD
[2888]314   call get_field("water_reservoir",water_reservoir,found)
315   if(.not.found) then
316      write(*,*)'Pemetat0: failed loading <water_reservoir>'
317      write(*,*)'will reconstruct the values from watercaptag'
318      do ig=1,ngrid
319        if(watercaptag(ig)) then
[2893]320           water_reservoir(ig)=water_reservoir_nom
[2888]321        else
[2893]322           water_reservoir(ig)=0.
[2888]323        endif
324      enddo
325   endif
326#endif
327
[2794]328call close_startphy
329
330else !No startfi, let's build all by hand
331
[3039]332    if (soil_pem) then
[2794]333
334!a) Thermal inertia
335   do islope = 1,nslope
336      do ig = 1,ngrid
337
[3076]338          if(TI_PEM(ig,index_breccia,islope).lt.TI_breccia) then
[2794]339!!! transition
[2895]340             delta = depth_breccia
341             TI_PEM(ig,index_breccia+1,islope) =sqrt((layer_PEM(index_breccia+1)-layer_PEM(index_breccia))/ &
342            (((delta-layer_PEM(index_breccia))/(TI_PEM(ig,index_breccia,islope)**2))+ &
343                      ((layer_PEM(index_breccia+1)-delta)/(TI_breccia**2))))
[2794]344
[2895]345          do iloop=index_breccia+2,index_bedrock
[2794]346            TI_PEM(ig,iloop,islope) = TI_breccia
[3076]347         enddo
[2794]348         else ! we keep the high ti values
[2895]349           do iloop=index_breccia+1,index_bedrock
350                  TI_PEM(ig,iloop,islope) = TI_PEM(ig,index_breccia,islope)
[3076]351           enddo
[2779]352         endif
353
[2794]354!! transition
[2895]355             delta = depth_bedrock
356             TI_PEM(ig,index_bedrock+1,islope) = sqrt((layer_PEM(index_bedrock+1)-layer_PEM(index_bedrock))/ &
357            (((delta-layer_PEM(index_bedrock))/(TI_PEM(ig,index_bedrock,islope)**2))+ &
358                      ((layer_PEM(index_bedrock+1)-delta)/(TI_breccia**2))))
359          do iloop=index_bedrock+2,nsoil_PEM
[2794]360            TI_PEM(ig,iloop,islope) = TI_bedrock
[3076]361         enddo
[2794]362      enddo
363enddo
[2779]364
[2794]365 do iloop = 1,nsoil_GCM
366   inertiedat_PEM(:,iloop) = inertiedat(:,iloop)
367 enddo
368!!! zone de transition
[3076]369delta = depth_breccia
[2794]370do ig = 1,ngrid
[3076]371      if(inertiedat_PEM(ig,index_breccia).lt.TI_breccia) then
[2895]372inertiedat_PEM(ig,index_breccia+1) = sqrt((layer_PEM(index_breccia+1)-layer_PEM(index_breccia))/ &
373            (((delta-layer_PEM(index_breccia))/(inertiedat(ig,index_breccia)**2))+ &
374                      ((layer_PEM(index_breccia+1)-delta)/(TI_breccia**2))))
[2779]375
376
[3076]377 do iloop = index_breccia+2,index_bedrock
[2779]378
[2794]379       inertiedat_PEM(ig,iloop) = TI_breccia
[3076]380
[2794]381 enddo
[3076]382else
383   do iloop = index_breccia+1,index_bedrock
[2895]384       inertiedat_PEM(ig,iloop) = inertiedat_PEM(ig,index_breccia)
[2794]385    enddo
[2779]386
[2794]387endif
388enddo
[2779]389
[2794]390!!! zone de transition
[2895]391delta = depth_bedrock
[2794]392do ig = 1,ngrid
[2895]393inertiedat_PEM(ig,index_bedrock+1) = sqrt((layer_PEM(index_bedrock+1)-layer_PEM(index_bedrock))/ &
394            (((delta-layer_PEM(index_bedrock))/(inertiedat_PEM(ig,index_bedrock)**2))+ &
395                      ((layer_PEM(index_bedrock+1)-delta)/(TI_bedrock**2))))
[2794]396enddo
[2779]397
398
399
[2895]400 do iloop = index_bedrock+2, nsoil_PEM
[2794]401   do ig = 1,ngrid
402      inertiedat_PEM(ig,iloop) = TI_bedrock
403   enddo
404 enddo
[2779]405
[3082]406write(*,*) 'PEMETAT0: TI done'
[2794]407
[3076]408!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
409!b) Soil temperature
[2794]410    do islope = 1,nslope
[2895]411!     do ig = 1,ngrid
412!        kcond = (TI_PEM(ig,index_breccia+1,islope)*TI_PEM(ig,index_breccia+1,islope))/volcapa
413!        tsoil_PEM(ig,index_breccia+1,islope) = tsoil_PEM(ig,index_breccia,islope) + fluxgeo/kcond*(mlayer_PEM(index_breccia)-mlayer_PEM(index_breccia-1))
414!
415!       do iloop=index_breccia+2,index_bedrock
416!            kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa
417!            tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_breccia+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_breccia))
418!      enddo
419!        kcond = (TI_PEM(ig,index_bedrock+1,islope)*TI_PEM(ig,index_bedrock+1,islope))/volcapa
420!        tsoil_PEM(ig,index_bedrock+1,islope) = tsoil_PEM(ig,index_bedrock,islope) + fluxgeo/kcond*(mlayer_PEM(index_bedrock)-mlayer_PEM(index_bedrock-1))
[2794]421
[2895]422!       do iloop=index_bedrock+2,nsoil_PEM
423!            kcond = (TI_PEM(ig,iloop,islope)*TI_PEM(ig,iloop,islope))/volcapa
424!            tsoil_PEM(ig,iloop,islope) = tsoil_PEM(ig,index_bedrock+1,islope) + fluxgeo/kcond*(mlayer_PEM(iloop-1)-mlayer_PEM(index_bedrock))
425!      enddo
[3076]426
[2895]427!       enddo
[2794]428
[2895]429      call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope))
[3076]430      call soil_pem_compute(ngrid,nsoil_PEM,.true.,TI_PEM(:,:,islope),timestep,tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope))
[3123]431 
432! First raw initialization
433      do it = 1,timelen
[2794]434        do isoil = nsoil_GCM+1,nsoil_PEM
[3123]435          tsoil_inst(:,isoil,islope,it) = tsoil_PEM(:,isoil,islope)
[2794]436        enddo
[3123]437      enddo
[3039]438
[3123]439      do it = 1,timelen
[3039]440        do isoil = nsoil_GCM+1,nsoil_PEM
[3123]441          call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_ave_yr2(:,islope),tsoil_inst(:,:,islope,it))
[2849]442        enddo
[3123]443       enddo
444
445       do isoil = nsoil_GCM+1,nsoil_PEM
446         do ig = 1,ngrid
447           watersoil_ave(ig,isoil,islope) = exp(beta_clap_h2o/tsoil_PEM(ig,isoil,islope) + alpha_clap_h2o)/tsoil_PEM(ig,isoil,islope)*mmol(igcm_h2o_vap)/(mugaz*r)
448         enddo
449       enddo
[2895]450enddo !islope
[3082]451write(*,*) 'PEMETAT0: TSOIL done'
[2849]452
[3076]453!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[3039]454!c) Ice table
[3123]455       ice_table(:,:) = -1.  ! by default, no ice table
456       ice_table_thickness(:,:) = -1.
[3039]457       call computeice_table_equilibrium(ngrid,nslope,nsoil_PEM,watercaptag,watersurf_ave,watersoil_ave,TI_PEM(:,1,:),ice_table,ice_table_thickness)
458       call update_soil_thermalproperties(ngrid,nslope,nsoil_PEM,tend_h2oglaciers,waterice,global_ave_pressure,ice_table,ice_table_thickness,TI_PEM)
459       do islope = 1,nslope
460         call soil_pem_ini(ngrid,nsoil_PEM,TI_PEM(:,:,islope),tsurf_ave_yr2(:,islope),tsoil_PEM(:,:,islope))
461       enddo
[3082]462       write(*,*) 'PEMETAT0: Ice table done'
[2794]463
[3076]464!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2794]465!d) Regolith adsorbed
[3076]466if (adsorption_pem) then
[2863]467    m_co2_regolith_phys(:,:,:) = 0.
468    m_h2o_regolith_phys(:,:,:) = 0.
469
470    call regolith_adsorption(ngrid,nslope,nsoil_PEM,timelen,tend_h2oglaciers,tend_co2glaciers,waterice,co2ice,tsoil_PEM,TI_PEM,ps_inst,q_co2,q_h2o, &
[3076]471                             m_h2o_regolith_phys,deltam_h2o_regolith_phys, m_co2_regolith_phys,deltam_co2_regolith_phys)
472
[2863]473    deltam_co2_regolith_phys(:) = 0.
[3076]474    deltam_h2o_regolith_phys(:) = 0.
475endif
[2863]476
[3082]477write(*,*) 'PEMETAT0: CO2 adsorption done'
[2835]478endif !soil_pem
[2794]479
[3076]480!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2888]481!. e) water reservoir
[3076]482#ifndef CPP_STD
483    do ig = 1,ngrid
484        if (watercaptag(ig)) then
485            water_reservoir(ig) = water_reservoir_nom
[2888]486        else
[3076]487            water_reservoir(ig) = 0.
[2888]488        endif
[3076]489    enddo
[2888]490#endif
491
[2893]492endif ! of if (startphy_file)
493
[3076]494if (soil_pem) then ! Sanity check
495    do ig = 1,ngrid
496        do islope = 1,nslope
497            do iloop = 1,nsoil_PEM
498                if (isnan(tsoil_PEM(ig,iloop,islope))) call abort_pem("PEM - pemetat0","NaN detected in Tsoil",1)
499            enddo
500        enddo
501    enddo
502endif !soil_pem
[2794]503
[3076]504END SUBROUTINE pemetat0
505
506END MODULE pemetat0_mod
507
Note: See TracBrowser for help on using the repository browser.