/[lmdze]/trunk/libf/phylmd/Mobidic/regr_pr_comb_coefoz.f90
ViewVC logotype

Diff of /trunk/libf/phylmd/Mobidic/regr_pr_comb_coefoz.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/libf/phylmd/read_coefoz_m.f90 revision 7 by guez, Mon Mar 31 12:24:17 2008 UTC trunk/libf/phylmd/Mobidic/regr_pr_comb_coefoz.f90 revision 17 by guez, Tue Aug 5 13:31:32 2008 UTC
# Line 7  module regr_pr_comb_coefoz_m Line 7  module regr_pr_comb_coefoz_m
7    
8    implicit none    implicit none
9    
10      ! The five module variables declared here are on the "physics" grid.
11      ! The value of each variable for index "(i, k)" is at longitude
12      ! "rlon(i)", latitude "rlat(i)" and middle of layer "k".
13    
14    real, save:: c_Mob(klon, llm)    real, save:: c_Mob(klon, llm)
15    ! (sum of Mobidic terms in the net mass production rate of ozone    ! (sum of Mobidic terms in the net mass production rate of ozone
16    ! by chemistry, per unit mass of air, in s-1)    ! by chemistry, per unit mass of air, in s-1)
   ! (On the "physics" grid.  
   ! "c_Mob(i, k)" is at longitude "rlon(i)", latitude "rlat(i)",  
   ! middle of layer "k".)  
17    
18    real, save:: a2(klon, llm)    real, save:: a2(klon, llm)
19    ! (derivative of mass production rate of ozone per unit mass of    ! (derivative of mass production rate of ozone per unit mass of
20    ! air with respect to ozone mass fraction, in s-1)    ! air with respect to ozone mass fraction, in s-1)
   ! (On the "physics" grid.  
   ! "a2(i, k)" is at longitude "rlon(i)", latitude "rlat(i)",  
   ! middle of layer "k".)  
21    
22    real, save:: a4_mass(klon, llm)    real, save:: a4_mass(klon, llm)
23    ! (derivative of mass production rate of ozone per unit mass of    ! (derivative of mass production rate of ozone per unit mass of
24    ! air with respect to temperature, in s-1 K-1)    ! air with respect to temperature, in s-1 K-1)
   ! (On the "physics" grid.  
   ! "a4_mass(i, k)" is at longitude "rlon(i)", latitude "rlat(i)",  
   ! middle of layer "k".)  
25    
26    real, save:: a6_mass(klon, llm)    real, save:: a6_mass(klon, llm)
27    ! (derivative of mass production rate of ozone per unit mass of    ! (derivative of mass production rate of ozone per unit mass of
28    ! air with respect to mass column-density of ozone above, in m2 s-1 kg-1)    ! air with respect to mass column-density of ozone above, in m2 s-1 kg-1)
   ! (On the "physics" grid.  
   ! "a6_mass(i, k)" is at longitude "rlon(i)", latitude "rlat(i)",  
   ! middle of layer "k".)  
29    
30    real, save:: r_het_interm(klon, llm)    real, save:: r_het_interm(klon, llm)
31    ! (net mass production rate by heterogeneous chemistry, per unit    ! (net mass production rate by heterogeneous chemistry, per unit
32    ! mass of ozone, corrected for chlorine content and latitude, but    ! mass of ozone, corrected for chlorine content and latitude, but
33    ! not for temperature and sun direction, in s-1)    ! not for temperature and sun direction, in s-1)
   ! (On the "physics" grid.  
   ! "r_het_interm(i, k)" is at longitude "rlon(i)", latitude "rlat(i)",  
   ! middle of layer "k".)  
34    
35    private klon, llm    private klon, llm
36    
# Line 53  contains Line 42  contains
42      ! coefficients ozone".      ! coefficients ozone".
43    
44      ! This subroutine :      ! This subroutine :
45      ! -- reads from a file all eight parameters for ozone chemistry,      ! -- reads from a file all eight coefficients for ozone chemistry,
46      !    at the current day ;      !    at the current day ;
47      ! -- regrids the parameters in pressure to the LMDZ vertical grid ;      ! -- regrids the coefficients in pressure to the LMDZ vertical grid ;
48      ! -- packs the parameters to the "physics" horizontal grid ;      ! -- packs the coefficients to the "physics" horizontal grid ;
49      ! -- combines the eight parameters to define the five module variables.      ! -- combines the eight coefficients to define the five module variables.
50    
51      ! We assume that, in "coefoz_LMDZ.nc", the pressure levels are in hPa      ! We assume that, in "coefoz_LMDZ.nc", the pressure levels are in hPa
52      ! and strictly increasing.      ! and strictly increasing.
# Line 72  contains Line 61  contains
61      ! Variables local to the procedure:      ! Variables local to the procedure:
62      integer ncid ! for NetCDF      integer ncid ! for NetCDF
63    
     real, pointer:: plev(:)  
     ! (pressure level of input data, converted to Pa, in strictly  
     ! increasing order)  
   
     integer n_plev ! number of pressure levels in the input data  
   
     real, allocatable:: press_in_edg(:)  
     ! (edges of pressure intervals for input data, in Pa, in strictly  
     ! increasing order)  
   
64      real coefoz(klon, llm)      real coefoz(klon, llm)
65      ! (temporary storage for an ozone coefficient)      ! (temporary storage for an ozone coefficient)
66      ! (On the "physics" grid.      ! (On the "physics" grid.
# Line 104  contains Line 83  contains
83    
84      !------------------------------------      !------------------------------------
85    
86      print *, "Call sequence information: read_coefoz"      print *, "Call sequence information: regr_pr_comb_coefoz"
87    
88      call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid)      call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid)
89    
90      call nf95_get_coord(ncid, "plev", plev)      call regr_pr_av_coefoz(ncid, "a2", julien, a2)
     ! Convert from hPa to Pa because "regr_pr_av" and "regr_pr_int" require so:  
     plev = plev * 100.  
     n_plev = size(plev)  
   
     ! Compute edges of pressure intervals:  
     allocate(press_in_edg(n_plev + 1))  
     press_in_edg(1) = 0.  
     ! We choose edges halfway in logarithm:  
     forall (k = 2:n_plev) press_in_edg(k) = sqrt(plev(k - 1) * plev(k))  
     press_in_edg(n_plev + 1) = huge(0.)  
     ! (infinity, but any value guaranteed to be greater than the  
     ! surface pressure would do)  
   
     call regr_pr_av_coefoz(ncid, "a2", julien, press_in_edg, a2)  
91    
92      call regr_pr_av_coefoz(ncid, "a4", julien, press_in_edg, a4_mass)      call regr_pr_av_coefoz(ncid, "a4", julien, a4_mass)
93      a4_mass = a4_mass * 48. / 29.      a4_mass = a4_mass * 48. / 29.
94    
95      call regr_pr_av_coefoz(ncid, "a6", julien, press_in_edg, a6)      call regr_pr_av_coefoz(ncid, "a6", julien, a6)
96    
97      ! Compute "a6_mass" avoiding underflow, do not divide by 1e4      ! Compute "a6_mass" avoiding underflow, do not divide by 1e4
98      ! before dividing by molecular mass:      ! before dividing by molecular mass:
# Line 138  contains Line 103  contains
103      ! (We use as few local variables as possible, in order to spare      ! (We use as few local variables as possible, in order to spare
104      ! main memory.)      ! main memory.)
105    
106      call regr_pr_av_coefoz(ncid, "P_net_Mob", julien, press_in_edg, c_Mob)      call regr_pr_av_coefoz(ncid, "P_net_Mob", julien, c_Mob)
107    
108      call regr_pr_av_coefoz(ncid, "r_Mob", julien, press_in_edg, coefoz)      call regr_pr_av_coefoz(ncid, "r_Mob", julien, coefoz)
109      c_mob = c_mob - a2 * coeofoz      c_mob = c_mob - a2 * coefoz
110    
111      call regr_pr_int_coefoz(ncid, "Sigma_Mob", julien, plev, top_value=0., &      call regr_pr_int_coefoz(ncid, "Sigma_Mob", julien, top_value=0., v3=coefoz)
          coefoz)  
112      c_mob = (c_mob - a6 * coefoz) * 48. / 29.      c_mob = (c_mob - a6 * coefoz) * 48. / 29.
113    
114      call regr_pr_av_coefoz(ncid, "temp_Mob", julien, press_in_edg, coefoz)      call regr_pr_av_coefoz(ncid, "temp_Mob", julien, coefoz)
115      c_mob = c_mob - a4_mass * coefoz      c_mob = c_mob - a4_mass * coefoz
116    
117      call regr_pr_av_coefoz(ncid, "R_Het", julien, press_in_edg, r_het_interm)      call regr_pr_av_coefoz(ncid, "R_Het", julien, r_het_interm)
118      ! Heterogeneous chemistry is only at high latitudes:      ! Heterogeneous chemistry is only at high latitudes:
119      forall (k = 1: llm)      forall (k = 1: llm)
120         where (abs(rlat) <= 45.) r_het_interm(:, k) = 0.         where (abs(rlat) <= 45.) r_het_interm(:, k) = 0.
121      end forall      end forall
122      where (r_het_interm  /= 0.) r_het_interm = r_het_interm * (Clx / 3.8e-9)**2      r_het_interm = r_het_interm * (Clx / 3.8e-9)**2
123    
     deallocate(plev) ! pointer  
124      call nf95_close(ncid)      call nf95_close(ncid)
125    
126    end subroutine regr_pr_comb_coefoz    end subroutine regr_pr_comb_coefoz

Legend:
Removed from v.7  
changed lines
  Added in v.17

  ViewVC Help
Powered by ViewVC 1.1.21