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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 52 - (show annotations)
Fri Sep 23 12:28:01 2011 UTC (12 years, 7 months ago) by guez
File size: 4030 byte(s)
Split "conflx.f" into single-procedure files in directory "Conflx".

Split "cv_routines.f" into single-procedure files in directory
"CV_routines". Made module "cvparam" from included file
"cvparam.h". No included file other than "netcdf.inc" left in LMDZE.

1 module regr_pr_comb_coefoz_m
2
3 use dimens_m, only: llm
4 use dimphy, only: klon
5
6 implicit none
7
8 ! The five module variables declared here are on the "physics" grid.
9 ! The value of each variable for index "(i, k)" is at longitude
10 ! "rlon(i)", latitude "rlat(i)" and middle of layer "k".
11
12 real, save:: c_Mob(klon, llm)
13 ! (sum of Mobidic terms in the net mass production rate of ozone
14 ! by chemistry, per unit mass of air, in s-1)
15
16 real, save:: a2(klon, llm)
17 ! (derivative of mass production rate of ozone per unit mass of
18 ! air with respect to ozone mass fraction, in s-1)
19
20 real, save:: a4_mass(klon, llm)
21 ! (derivative of mass production rate of ozone per unit mass of
22 ! air with respect to temperature, in s-1 K-1)
23
24 real, save:: a6_mass(klon, llm)
25 ! (derivative of mass production rate of ozone per unit mass of
26 ! air with respect to mass column-density of ozone above, in m2 s-1 kg-1)
27
28 real, save:: r_het_interm(klon, llm)
29 ! (net mass production rate by heterogeneous chemistry, per unit
30 ! mass of ozone, corrected for chlorine content and latitude, but
31 ! not for temperature and sun direction, in s-1)
32
33 private klon, llm
34
35 contains
36
37 subroutine regr_pr_comb_coefoz(julien)
38
39 ! "regr_pr_comb_coefoz" stands for "regrid pressure combine
40 ! coefficients ozone".
41
42 ! This subroutine :
43 ! -- reads from a file all eight coefficients for ozone chemistry,
44 ! at the current day ;
45 ! -- regrids the coefficients in pressure to the LMDZ vertical grid ;
46 ! -- packs the coefficients to the "physics" horizontal grid ;
47 ! -- combines the eight coefficients to define the five module variables.
48
49 use netcdf95, only: nf95_open, nf95_close
50 use netcdf, only: nf90_nowrite
51 use regr_pr_coefoz, only: regr_pr_av_coefoz, regr_pr_int_coefoz
52 use phyetat0_m, only: rlat
53
54 integer, intent(in):: julien ! jour julien, 1 <= julien <= 360
55
56 ! Variables local to the procedure:
57
58 integer ncid ! for NetCDF
59
60 real coefoz(klon, llm)
61 ! (temporary storage for an ozone coefficient)
62 ! (On the "physics" grid.
63 ! "coefoz(i, k)" is at longitude "rlon(i)", latitude "rlat(i)",
64 ! middle of layer "k".)
65
66 real a6(klon, llm)
67 ! (derivative of "P_net_Mob" with respect to column-density of ozone
68 ! above, in cm2 s-1)
69 ! (On the "physics" grid.
70 ! "a6(i, k)" is at longitude "rlon(i)", latitude "rlat(i)",
71 ! middle of layer "k".)
72
73 real, parameter:: amu = 1.6605402e-27 ! atomic mass unit, in kg
74
75 real, parameter:: Clx = 3.8e-9
76 ! (total chlorine content in the upper stratosphere)
77
78 integer k
79
80 !------------------------------------
81
82 print *, "Call sequence information: regr_pr_comb_coefoz"
83
84 call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid)
85
86 call regr_pr_av_coefoz(ncid, "a2", julien, a2)
87
88 call regr_pr_av_coefoz(ncid, "a4", julien, a4_mass)
89 a4_mass = a4_mass * 48. / 29.
90
91 call regr_pr_av_coefoz(ncid, "a6", julien, a6)
92
93 ! Compute "a6_mass" avoiding underflow, do not divide by 1e4
94 ! before dividing by molecular mass:
95 a6_mass = a6 / (1e4 * 29. * amu)
96 ! (factor 1e4: conversion from cm2 to m2)
97
98 ! Combine coefficients to get "c_Mob":
99 ! (We use as few local variables as possible, in order to spare
100 ! main memory.)
101
102 call regr_pr_av_coefoz(ncid, "P_net_Mob", julien, c_Mob)
103
104 call regr_pr_av_coefoz(ncid, "r_Mob", julien, coefoz)
105 c_mob = c_mob - a2 * coefoz
106
107 call regr_pr_int_coefoz(ncid, "Sigma_Mob", julien, top_value=0., v3=coefoz)
108 c_mob = (c_mob - a6 * coefoz) * 48. / 29.
109
110 call regr_pr_av_coefoz(ncid, "temp_Mob", julien, coefoz)
111 c_mob = c_mob - a4_mass * coefoz
112
113 call regr_pr_av_coefoz(ncid, "R_Het", julien, r_het_interm)
114 ! Heterogeneous chemistry is only at high latitudes:
115 forall (k = 1: llm)
116 where (abs(rlat) <= 45.) r_het_interm(:, k) = 0.
117 end forall
118 r_het_interm = r_het_interm * (Clx / 3.8e-9)**2
119
120 call nf95_close(ncid)
121
122 end subroutine regr_pr_comb_coefoz
123
124 end module regr_pr_comb_coefoz_m

  ViewVC Help
Powered by ViewVC 1.1.21