source: LMDZ6/trunk/libf/phylmd/o3_chem_m.f90 @ 5846

Last change on this file since 5846 was 5837, checked in by rkazeroni, 3 months ago

For GPU porting of angle and zenang routines:

  • Put routine into module (speeds up source-to-source transformation)
  • Add "horizontal" comment to specify possible names of horizontal variables


  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 5.5 KB
RevLine 
[1379]1! $Id$
2module o3_chem_m
3
4  IMPLICIT none
5
6  private o3_prod
7
8contains
9
10  subroutine o3_chem(julien, gmtime, t_seri, zmasse, pdtphys, rlat, rlon, q)
11
12    ! This procedure evolves the ozone mass fraction through a time
13    ! step taking only chemistry into account.
14
15    ! All the 2-dimensional arrays are on the partial "physics" grid.
[2346]16    ! Their shape is "(/klon, nbp_lev/)".
[1379]17    ! Index "(i, :)" is for longitude "rlon(i)", latitude "rlat(i)".
18
19    use assert_m, only: assert
20    use dimphy, only: klon
21    use regr_pr_comb_coefoz_m, only: c_Mob, a4_mass, a2, r_het_interm
[2346]22    use mod_grid_phy_lmdz, only: nbp_lev
23    use nrtype, only: pi
[5837]24    USE orbite_mod, ONLY: orbite, zenang
[1379]25
26    integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
[5390]27    real, intent(in):: gmtime ! heure de la journee en fraction de jour
[2346]28    real, intent(in):: t_seri(:, :) ! (klon, nbp_lev) temperature, in K
[1379]29
[2346]30    real, intent(in):: zmasse(:, :) ! (klon, nbp_lev)
[1379]31    ! (column-density of mass of air in a cell, in kg m-2)
32    ! "zmasse(:, k)" is for layer "k".)
33
34    real, intent(in):: pdtphys ! time step for physics, in s
35
36    REAL, intent(in):: rlat(:), rlon(:)
37    ! (longitude and latitude of each horizontal position, in degrees)
38
[2346]39    real, intent(inout):: q(:, :) ! (klon, nbp_lev) mass fraction of ozone
[1379]40    ! "q(:, k)" is at middle of layer "k".)
41
42    ! Variables local to the procedure:
43    ! (for "pi")
44    integer k
45
[2346]46    real c(klon, nbp_lev)
[1379]47    ! (constant term during a time step in the net mass production
48    ! rate of ozone by chemistry, per unit mass of air, in s-1)
49    ! "c(:, k)" is at middle of layer "k".)
50
[2346]51    real b(klon, nbp_lev)
[1379]52    ! (coefficient of "q" in the net mass production
53    ! rate of ozone by chemistry, per unit mass of air, in s-1)
54    ! "b(:, k)" is at middle of layer "k".)
55
[2346]56    real dq_o3_chem(klon, nbp_lev)
[1379]57    ! (variation of ozone mass fraction due to chemistry during a time step)
58    ! "dq_o3_chem(:, k)" is at middle of layer "k".)
59
60    real earth_long
61    ! (longitude vraie de la Terre dans son orbite solaire, par
[5390]62    ! rapport au point vernal (21 mars), en degres)
[1379]63
64    real pmu0(klon) ! mean of cosine of solar zenith angle during "pdtphys"
65    real trash1
66    real trash2(klon)
67
68    !-------------------------------------------------------------
69
70    call assert(klon == (/size(q, 1), size(t_seri, 1), size(zmasse, 1), &
71         size(rlat), size(rlon)/), "o3_chem klon")
[2346]72    call assert(nbp_lev == (/size(q, 2), size(t_seri, 2), size(zmasse, 2)/), &
73         "o3_chem nbp_lev")
[1379]74
75    c = c_Mob + a4_mass * t_seri
76
77    ! Compute coefficient "b":
78
79    ! Heterogeneous chemistry is only at low temperature:
80    where (t_seri < 195.)
81       b = r_het_interm
82    elsewhere
83       b = 0.
84    end where
85
86    ! Heterogeneous chemistry is only during daytime:
87    call orbite(real(julien), earth_long, trash1)
[4103]88    call zenang(earth_long, gmtime, 0., pdtphys, rlat, rlon, pmu0, trash2)
[2346]89    forall (k = 1: nbp_lev)
[1379]90       where (pmu0 <= cos(87. / 180. * pi)) b(:, k) = 0.
91    end forall
92
93    b = b + a2
94
95    ! Midpoint method:
96
97    ! Trial step to the midpoint:
98    dq_o3_chem = o3_prod(q, zmasse, c, b) * pdtphys  / 2
99    ! "Real" step across the whole interval:
100    dq_o3_chem = o3_prod(q + dq_o3_chem, zmasse, c, b) * pdtphys
101    q = q + dq_o3_chem
102
103    ! Confine the mass fraction:
104    q = min(max(q, 0.), .01)
105
106  end subroutine o3_chem
107
108  !*************************************************
109
110  function o3_prod(q, zmasse, c, b)
111
112    ! This function computes the production rate of ozone by chemistry.
113
114    ! All the 2-dimensional arrays are on the partial "physics" grid.
[2346]115    ! Their shape is "(/klon, nbp_lev/)".
[1379]116    ! Index "(i, :)" is for longitude "rlon(i)", latitude "rlat(i)".
117
118    use regr_pr_comb_coefoz_m, only: a6_mass
119    use assert_m, only: assert
120    use dimphy, only: klon
[2346]121    use mod_grid_phy_lmdz, only: nbp_lev
[1379]122
123    real, intent(in):: q(:, :) ! mass fraction of ozone
124    ! "q(:, k)" is at middle of layer "k".)
125
126    real, intent(in):: zmasse(:, :)
127    ! (column-density of mass of air in a layer, in kg m-2)
128    ! ("zmasse(:, k)" is for layer "k".)
129
130    real, intent(in):: c(:, :)
131    ! (constant term during a time step in the net mass production
132    ! rate of ozone by chemistry, per unit mass of air, in s-1)
133    ! "c(:, k)" is at middle of layer "k".)
134
135    real, intent(in):: b(:, :)
136    ! (coefficient of "q" in the net mass production rate of ozone by
137    ! chemistry, per unit mass of air, in s-1)
138    ! ("b(:, k)" is at middle of layer "k".)
139
[2346]140    real o3_prod(klon, nbp_lev)
[1379]141    ! (net mass production rate of ozone by chemistry, per unit mass
142    ! of air, in s-1)
143    ! ("o3_prod(:, k)" is at middle of layer "k".)
144
145    ! Variables local to the procedure:
146
[2346]147    real sigma_mass(klon, nbp_lev)
[1379]148    ! (mass column-density of ozone above point, in kg m-2)
149    ! ("sigma_mass(:, k)" is at middle of layer "k".)
150
151    integer k
152
153    !-------------------------------------------------------------------
154
155    call assert(klon == (/size(q, 1), size(zmasse, 1), size(c, 1), &
156         size(b, 1)/), "o3_prod 1")
[2346]157    call assert(nbp_lev == (/size(q, 2), size(zmasse, 2), size(c, 2), &
[1379]158         size(b, 2)/), "o3_prod 2")
159
160    ! Compute the column-density above the base of layer
161    ! "k", and, as a first approximation, take it as column-density
162    ! above the middle of layer "k":
[2346]163    sigma_mass(:, nbp_lev) = zmasse(:, nbp_lev) * q(:, nbp_lev) ! top layer
164    do k =  nbp_lev - 1, 1, -1
[1379]165       sigma_mass(:, k) = sigma_mass(:, k+1) + zmasse(:, k) * q(:, k)
166    end do
167
168    o3_prod = c + b * q + a6_mass * sigma_mass
169
170  end function o3_prod
171
172end module o3_chem_m
Note: See TracBrowser for help on using the repository browser.