1 | ! $Id$ |
---|
2 | module regr_pr_comb_coefoz_m |
---|
3 | |
---|
4 | implicit none |
---|
5 | |
---|
6 | ! The five module variables declared here are on the partial |
---|
7 | ! "physics" grid. |
---|
8 | ! The value of each variable for index "(i, k)" is at longitude |
---|
9 | ! "rlon(i)", latitude "rlat(i)" and middle of layer "k". |
---|
10 | |
---|
11 | real, allocatable, save:: c_Mob(:, :) |
---|
12 | ! (sum of Mobidic terms in the net mass production rate of ozone |
---|
13 | ! by chemistry, per unit mass of air, in s-1) |
---|
14 | |
---|
15 | real, allocatable, save:: a2(:, :) |
---|
16 | ! (derivative of mass production rate of ozone per unit mass of |
---|
17 | ! air with respect to ozone mass fraction, in s-1) |
---|
18 | |
---|
19 | real, allocatable, save:: a4_mass(:, :) |
---|
20 | ! (derivative of mass production rate of ozone per unit mass of |
---|
21 | ! air with respect to temperature, in s-1 K-1) |
---|
22 | |
---|
23 | real, allocatable, save:: a6_mass(:, :) |
---|
24 | ! (derivative of mass production rate of ozone per unit mass of |
---|
25 | ! air with respect to mass column-density of ozone above, in m2 s-1 kg-1) |
---|
26 | |
---|
27 | real, allocatable, save:: r_het_interm(:, :) |
---|
28 | ! (net mass production rate by heterogeneous chemistry, per unit |
---|
29 | ! mass of ozone, corrected for chlorine content and latitude, but |
---|
30 | ! not for temperature and sun direction, in s-1) |
---|
31 | |
---|
32 | !$omp threadprivate(c_Mob, a2, a4_mass, a6_mass, r_het_interm) |
---|
33 | |
---|
34 | contains |
---|
35 | |
---|
36 | subroutine alloc_coefoz |
---|
37 | |
---|
38 | ! This procedure is called once per run. |
---|
39 | ! It allocates module variables. |
---|
40 | |
---|
41 | use dimphy, only: klon |
---|
42 | |
---|
43 | ! Variables local to the procedure: |
---|
44 | include "dimensions.h" |
---|
45 | |
---|
46 | !--------------------------------------- |
---|
47 | |
---|
48 | !$omp master |
---|
49 | print *, "Call sequence information: alloc_coefoz" |
---|
50 | !$omp end master |
---|
51 | allocate(c_Mob(klon, llm), a2(klon, llm), a4_mass(klon, llm)) |
---|
52 | allocate(a6_mass(klon, llm), r_het_interm(klon, llm)) |
---|
53 | |
---|
54 | end subroutine alloc_coefoz |
---|
55 | |
---|
56 | !******************************************************* |
---|
57 | |
---|
58 | subroutine regr_pr_comb_coefoz(julien, rlat, paprs, pplay) |
---|
59 | |
---|
60 | ! "regr_pr_comb_coefoz" stands for "regrid pressure combine |
---|
61 | ! coefficients ozone". |
---|
62 | |
---|
63 | ! In this subroutine: |
---|
64 | ! -- the master thread of the root process reads from a file all |
---|
65 | ! eight coefficients for ozone chemistry, at the current day; |
---|
66 | ! -- the coefficients are packed to the "physics" horizontal grid |
---|
67 | ! and scattered to all threads of all processes; |
---|
68 | ! -- in all the threads of all the processes, the coefficients are |
---|
69 | ! regridded in pressure to the LMDZ vertical grid; |
---|
70 | ! -- in all the threads of all the processes, the eight |
---|
71 | ! coefficients are combined to define the five module variables. |
---|
72 | |
---|
73 | use netcdf95, only: nf95_open, nf95_close |
---|
74 | use netcdf, only: nf90_nowrite |
---|
75 | use assert_m, only: assert |
---|
76 | use dimphy, only: klon |
---|
77 | use mod_phys_lmdz_mpi_data, only: is_mpi_root |
---|
78 | use regr_pr_av_m, only: regr_pr_av |
---|
79 | use regr_pr_int_m, only: regr_pr_int |
---|
80 | use press_coefoz_m, only: press_in_edg, plev |
---|
81 | |
---|
82 | integer, intent(in):: julien ! jour julien, 1 <= julien <= 360 |
---|
83 | |
---|
84 | REAL, intent(in):: rlat(:) |
---|
85 | ! (latitude on the partial "physics" grid, in degrees) |
---|
86 | |
---|
87 | real, intent(in):: paprs(:, :) ! (klon, llm + 1) |
---|
88 | ! (pression pour chaque inter-couche, en Pa) |
---|
89 | |
---|
90 | real, intent(in):: pplay(:, :) ! (klon, llm) |
---|
91 | ! (pression pour le mileu de chaque couche, en Pa) |
---|
92 | |
---|
93 | ! Variables local to the procedure: |
---|
94 | |
---|
95 | include "dimensions.h" |
---|
96 | integer ncid ! for NetCDF |
---|
97 | |
---|
98 | real coefoz(klon, llm, 7) |
---|
99 | ! (temporary storage for 7 ozone coefficients) |
---|
100 | ! (On the partial "physics" grid. |
---|
101 | ! "coefoz(i, k, :)" is at longitude "rlon(i)", latitude "rlat(i)", |
---|
102 | ! middle of layer "k".) |
---|
103 | |
---|
104 | real a6(klon, llm) |
---|
105 | ! (derivative of "P_net_Mob" with respect to column-density of ozone |
---|
106 | ! above, in cm2 s-1) |
---|
107 | ! (On the partial "physics" grid. |
---|
108 | ! "a6(i, k)" is at longitude "rlon(i)", latitude "rlat(i)", |
---|
109 | ! middle of layer "k".) |
---|
110 | |
---|
111 | real, parameter:: amu = 1.6605402e-27 ! atomic mass unit, in kg |
---|
112 | |
---|
113 | real, parameter:: Clx = 3.8e-9 |
---|
114 | ! (total chlorine content in the upper stratosphere) |
---|
115 | |
---|
116 | integer k |
---|
117 | |
---|
118 | !------------------------------------ |
---|
119 | |
---|
120 | !!print *, "Call sequence information: regr_pr_comb_coefoz" |
---|
121 | call assert((/size(rlat), size(paprs, 1), size(pplay, 1)/) == klon, & |
---|
122 | "regr_pr_comb_coefoz klon") |
---|
123 | call assert((/size(paprs, 2) - 1, size(pplay, 2)/) == llm, & |
---|
124 | "regr_pr_comb_coefoz llm") |
---|
125 | |
---|
126 | !$omp master |
---|
127 | if (is_mpi_root) call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid) |
---|
128 | !$omp end master |
---|
129 | |
---|
130 | call regr_pr_av(ncid, (/"a2 ", "a4 ", "a6 ", & |
---|
131 | "P_net_Mob", "r_Mob ", "temp_Mob ", "R_Het "/), julien, & |
---|
132 | press_in_edg, paprs, coefoz) |
---|
133 | a2 = coefoz(:, :, 1) |
---|
134 | a4_mass = coefoz(:, :, 2) * 48. / 29. |
---|
135 | |
---|
136 | ! Compute "a6_mass" avoiding underflow, do not divide by 1e4 |
---|
137 | ! before dividing by molecular mass: |
---|
138 | a6_mass = coefoz(:, :, 3) / (1e4 * 29. * amu) |
---|
139 | ! (factor 1e4: conversion from cm2 to m2) |
---|
140 | |
---|
141 | ! We can overwrite "coefoz(:, :, 1)", which was saved to "a2": |
---|
142 | call regr_pr_int(ncid, "Sigma_Mob", julien, plev, pplay, top_value=0., & |
---|
143 | v3=coefoz(:, :, 1)) |
---|
144 | |
---|
145 | ! Combine coefficients to get "c_Mob": |
---|
146 | c_mob = (coefoz(:, :, 4) - a2 * coefoz(:, :, 5) & |
---|
147 | - coefoz(:, :, 3) * coefoz(:, :, 1)) * 48. / 29. & |
---|
148 | - a4_mass * coefoz(:, :, 6) |
---|
149 | |
---|
150 | r_het_interm = coefoz(:, :, 7) |
---|
151 | ! Heterogeneous chemistry is only at high latitudes: |
---|
152 | forall (k = 1: llm) |
---|
153 | where (abs(rlat) <= 45.) r_het_interm(:, k) = 0. |
---|
154 | end forall |
---|
155 | r_het_interm = r_het_interm * (Clx / 3.8e-9)**2 |
---|
156 | |
---|
157 | !$omp master |
---|
158 | if (is_mpi_root) call nf95_close(ncid) |
---|
159 | !$omp end master |
---|
160 | |
---|
161 | end subroutine regr_pr_comb_coefoz |
---|
162 | |
---|
163 | end module regr_pr_comb_coefoz_m |
---|