source: trunk/LMDZ.COMMON/libf/evolution/recomp_tend_co2_slope_mod.F90 @ 3554

Last change on this file since 3554 was 3554, checked in by jbclement, 6 days ago

PEM:
Follow-up of previous commit (r3553).
JBC

File size: 2.8 KB
Line 
1MODULE recomp_tend_co2_slope_mod
2
3implicit none
4
5!=======================================================================
6contains
7!=======================================================================
8
9SUBROUTINE recomp_tend_co2(ngrid,nslope,timelen,d_co2ice_phys,d_co2ice_ini,co2ice,emissivity, &
10                           vmr_co2_PCM,vmr_co2_PEM,ps_PCM_2,global_avg_press_PCM,global_avg_press_new)
11
12use constants_marspem_mod, only : alpha_clap_co2, beta_clap_co2, sigmaB, Lco2, sols_per_my, sec_per_sol
13
14implicit none
15
16!=======================================================================
17!
18!  Routine that compute the evolution of the tendencie for co2 ice
19!
20!=======================================================================
21
22!   arguments:
23!   ----------
24!   INPUT
25integer,                        intent(in) :: timelen, ngrid, nslope
26real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PCM          ! physical point field: Volume mixing ratio of co2 in the first layer
27real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PEM          ! physical point field: Volume mixing ratio of co2 in the first layer
28real, dimension(ngrid,timelen), intent(in) :: ps_PCM_2             ! physical point field: Surface pressure in the PCM
29real,                           intent(in) :: global_avg_press_PCM ! global averaged pressure at previous timestep
30real,                           intent(in) :: global_avg_press_new ! global averaged pressure at current timestep
31real, dimension(ngrid,nslope),  intent(in) :: d_co2ice_ini         ! physical point field: Evolution of perennial ice over one year
32real, dimension(ngrid,nslope),  intent(in) :: co2ice               ! CO2 ice per mesh and sub-grid slope (kg/m^2)
33real, dimension(ngrid,nslope),  intent(in) :: emissivity           ! Emissivity per mesh and sub-grid slope(1)
34!   OUTPUT
35real, dimension(ngrid,nslope), intent(inout) :: d_co2ice_phys ! physical point field: Evolution of perennial ice over one year
36
37!   local:
38!   ------
39integer :: i, t, islope
40real    :: coef, ave
41
42write(*,*) "Update of the CO2 tendency from the current pressure"
43
44! Evolution of the water ice for each physical point
45do i = 1,ngrid
46    do islope = 1,nslope
47        coef = sols_per_my*sec_per_sol*emissivity(i,islope)*sigmaB/Lco2
48        ave = 0.
49        if (co2ice(i,islope) > 1.e-4 .and. abs(d_co2ice_phys(i,islope)) > 1.e-5) then
50            do t = 1,timelen
51                ave = ave + (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PCM(i,t)*ps_PCM_2(i,t)/100.)))**4 &
52                      - (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PEM(i,t)*ps_PCM_2(i,t)*(global_avg_press_new/global_avg_press_PCM)/100.)))**4
53            enddo
54            if (ave < 1.e-4) ave = 0.
55            d_co2ice_phys(i,islope) = d_co2ice_ini(i,islope) - coef*ave/timelen
56        endif
57    enddo
58enddo
59
60END SUBROUTINE recomp_tend_co2
61
62END MODULE recomp_tend_co2_slope_mod
Note: See TracBrowser for help on using the repository browser.