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

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

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

revision 3 by guez, Wed Feb 27 13:16:39 2008 UTC revision 7 by guez, Mon Mar 31 12:24:17 2008 UTC
# Line 38  contains Line 38  contains
38      ! layer "k".)      ! layer "k".)
39    
40      ! Variables local to the procedure:      ! Variables local to the procedure:
41      integer month, k      integer k
42    
43      real c(klon, llm)      real c(klon, llm)
44      ! (constant term during a time step in the net mass production      ! (constant term during a time step in the net mass production
# Line 73  contains Line 73  contains
73      call assert(llm == (/size(q, 2), size(t_seri, 2), size(zmasse, 2)/), &      call assert(llm == (/size(q, 2), size(t_seri, 2), size(zmasse, 2)/), &
74           "o3_chem llm")           "o3_chem llm")
75    
76      month = (julien - 1) / 30 + 1 ! compute the month from the day number      c = c_Mob + a4_mass * t_seri
     c = c_Mob(:, :, month) + a4_mass(:, :, month) * t_seri  
77    
78      ! Compute coefficient "b":      ! Compute coefficient "b":
79    
80      ! Heterogeneous chemistry is only at low temperature:      ! Heterogeneous chemistry is only at low temperature:
81      where (t_seri < 195.)      where (t_seri < 195.)
82         b = r_het_interm(:, :, month)         b = r_het_interm
83      elsewhere      elsewhere
84         b = 0.         b = 0.
85      end where      end where
# Line 92  contains Line 91  contains
91         where (pmu0 <= cos(87. / 180. * pi)) b(:, k) = 0.         where (pmu0 <= cos(87. / 180. * pi)) b(:, k) = 0.
92      end forall      end forall
93    
94      b = b + a2(:, :, month)      b = b + a2
95    
96      ! Midpoint method:      ! Midpoint method:
97    
98      ! Trial step to the midpoint:      ! Trial step to the midpoint:
99      dq_o3_chem = o3_prod(q, month, zmasse, c, b) * pdtphys  / 2      dq_o3_chem = o3_prod(q, zmasse, c, b) * pdtphys  / 2
100      ! "Real" step across the whole interval:      ! "Real" step across the whole interval:
101      dq_o3_chem = o3_prod(q + dq_o3_chem, month, zmasse, c, b) * pdtphys      dq_o3_chem = o3_prod(q + dq_o3_chem, zmasse, c, b) * pdtphys
102      q = q + dq_o3_chem      q = q + dq_o3_chem
103    
104      ! Confine the mass fraction:      ! Confine the mass fraction:
# Line 109  contains Line 108  contains
108    
109    !*************************************************    !*************************************************
110    
111    function o3_prod(q, month, zmasse, c, b)    function o3_prod(q, zmasse, c, b)
112    
113      ! This function computes the production rate of ozone by chemistry.      ! This function computes the production rate of ozone by chemistry.
114    
# Line 123  contains Line 122  contains
122      ! "q(i, k)" is at longitude "rlon(i)", latitude "rlat(i)", middle of      ! "q(i, k)" is at longitude "rlon(i)", latitude "rlat(i)", middle of
123      ! layer "k".)      ! layer "k".)
124    
     integer, intent(in):: month  
   
125      real, intent(in):: zmasse(:, :)      real, intent(in):: zmasse(:, :)
126      ! (column-density of mass of air in a layer, in kg m-2)      ! (column-density of mass of air in a layer, in kg m-2)
127      ! (On the "physics" grid.      ! (On the "physics" grid.
# Line 177  contains Line 174  contains
174         sigma_mass(:, k) = sigma_mass(:, k+1) + zmasse(:, k) * q(:, k)         sigma_mass(:, k) = sigma_mass(:, k+1) + zmasse(:, k) * q(:, k)
175      end do      end do
176    
177      o3_prod = c + b * q + a6_mass(:, :, month) * sigma_mass      o3_prod = c + b * q + a6_mass * sigma_mass
178    
179    end function o3_prod    end function o3_prod
180    

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

  ViewVC Help
Powered by ViewVC 1.1.21