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

Last change on this file since 3093 was 3076, checked in by jbclement, 17 months ago

PEM:
Big cleaning/improvements of the PEM:

  • Conversion of "abort_pem.F" and "soil_settings_PEM.F" into Fortran 90;
  • Transformation of every PEM subroutines into module;
  • Rewriting of many subroutines with modern Fortran syntax;
  • Correction of a bug in "pem.F90" when calling 'recomp_tend_co2_slope'. The arguments were given in disorder and emissivity was missing;
  • Update of "launch_pem.sh" in deftank.

JBC

File size: 2.9 KB
Line 
1MODULE recomp_tend_co2_slope_mod
2
3implicit none
4
5!=======================================================================
6contains
7!=======================================================================
8
9SUBROUTINE recomp_tend_co2_slope(ngrid,nslope,timelen,tendencies_co2_ice_phys,tendencies_co2_ice_phys_ini,co2ice_slope,emissivity_slope, &
10                                 vmr_co2_gcm,vmr_co2_pem,ps_GCM_2,global_ave_press_GCM,global_ave_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_gcm                 ! 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_GCM_2                    ! physical point field : Surface pressure in the GCM
29real,                           intent(in) :: global_ave_press_GCM        ! global averaged pressure at previous timestep
30real,                           intent(in) :: global_ave_press_new        ! global averaged pressure at current timestep
31real, dimension(ngrid,nslope),  intent(in) :: tendencies_co2_ice_phys_ini ! physical point field : Evolution of perenial ice over one year
32real, dimension(ngrid,nslope),  intent(in) :: co2ice_slope                ! CO2 ice per mesh and sub-grid slope(kg/m^2)
33real, dimension(ngrid,nslope),  intent(in) :: emissivity_slope            ! Emissivity per mesh and sub-grid slope(1)
34!   OUTPUT
35real, intent(inout) ::  tendencies_co2_ice_phys(ngrid,nslope) ! physical point field : Evolution of perenial ice over one year
36
37!   local:
38!   ----
39integer :: i, t, islope
40real    :: coef, ave
41
42! Evolution of the water ice for each physical point
43do i = 1,ngrid
44    do islope = 1,nslope
45        coef = sols_per_my*sec_per_sol*emissivity_slope(i,islope)*sigmaB/Lco2
46        ave = 0.
47        if (co2ice_slope(i,islope) > 1.e-4 .and. abs(tendencies_co2_ice_phys(i,islope)) > 1.e-5) then
48            do t=1,timelen
49                ave = ave + (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_gcm(i,t)*ps_GCM_2(i,t)/100.)))**4 &
50                      - (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_pem(i,t)*ps_GCM_2(i,t)*(global_ave_press_new/global_ave_press_GCM)/100.)))**4
51            enddo
52        endif
53        if (ave < 1e-4) ave = 0.
54        tendencies_co2_ice_phys(i,islope) = tendencies_co2_ice_phys_ini(i,islope) - coef*ave/timelen
55    enddo
56enddo
57
58END SUBROUTINE recomp_tend_co2_slope
59
60END MODULE recomp_tend_co2_slope_mod
Note: See TracBrowser for help on using the repository browser.