1 | MODULE nirco2abs_mod |
---|
2 | |
---|
3 | IMPLICIT NONE |
---|
4 | |
---|
5 | CONTAINS |
---|
6 | |
---|
7 | SUBROUTINE nirco2abs(ngrid,nlayer,pplay,dist_sol,nq,pq, |
---|
8 | $ mu0,fract,declin,pdtnirco2) |
---|
9 | |
---|
10 | use tracer_mod, only: igcm_co2, igcm_o |
---|
11 | use comgeomfi_h, only: sinlon, coslon, sinlat, coslat |
---|
12 | USE comcstfi_h, ONLY: pi |
---|
13 | USE time_phylmdz_mod, ONLY: daysec |
---|
14 | use nirdata_mod, only: npres, alfa, corgcm, oco21d, pres1d |
---|
15 | IMPLICIT NONE |
---|
16 | c======================================================================= |
---|
17 | c subject: |
---|
18 | c -------- |
---|
19 | c Computing heating rate due to |
---|
20 | c absorption by CO2 in the near-infrared |
---|
21 | c This version includes NLTE effects |
---|
22 | c |
---|
23 | c (Scheme to be described in Forget et al., JGR, 2003) |
---|
24 | c (old Scheme described in Forget et al., JGR, 1999) |
---|
25 | c |
---|
26 | c This version updated with a new functional fit, |
---|
27 | c see NLTE correction-factor of Lopez-Valverde et al (1998) |
---|
28 | c Stephen Lewis 2000 |
---|
29 | c |
---|
30 | c jul 2011 malv+fgg New corrections for NLTE implemented |
---|
31 | c 08/2002 : correction for bug when running with diurnal=F |
---|
32 | c |
---|
33 | c author: Frederic Hourdin 1996 |
---|
34 | c ------ |
---|
35 | c Francois Forget 1999 |
---|
36 | c |
---|
37 | c input: |
---|
38 | c ----- |
---|
39 | c ngrid number of gridpoint of horizontal grid |
---|
40 | c nlayer Number of layer |
---|
41 | c dist_sol sun-Mars distance (AU) |
---|
42 | c mu0(ngrid) |
---|
43 | c fract(ngrid) day fraction of the time interval |
---|
44 | c declin latitude of subslar point |
---|
45 | c |
---|
46 | c output: |
---|
47 | c ------- |
---|
48 | c |
---|
49 | c pdtnirco2(ngrid,nlayer) Heating rate (K/s) |
---|
50 | c |
---|
51 | c |
---|
52 | c======================================================================= |
---|
53 | c |
---|
54 | c 0. Declarations : |
---|
55 | c ------------------ |
---|
56 | c |
---|
57 | include "callkeys.h" |
---|
58 | |
---|
59 | c----------------------------------------------------------------------- |
---|
60 | c Input/Output |
---|
61 | c ------------ |
---|
62 | integer,intent(in) :: ngrid ! number of (horizontal) grid points |
---|
63 | integer,intent(in) :: nlayer ! number of atmospheric layers |
---|
64 | real,intent(in) :: pplay(ngrid,nlayer) ! Pressure |
---|
65 | real,intent(in) :: dist_sol ! Sun-Mars distance (in AU) |
---|
66 | integer,intent(in) :: nq ! number of tracers |
---|
67 | real,intent(in) :: pq(ngrid,nlayer,nq) ! tracers |
---|
68 | real,intent(in) :: mu0(ngrid) ! solar angle |
---|
69 | real,intent(in) :: fract(ngrid) ! day fraction of the time interval |
---|
70 | real,intent(in) :: declin ! latitude of sub-solar point |
---|
71 | |
---|
72 | real,intent(out) :: pdtnirco2(ngrid,nlayer) ! heating rate (K/s) |
---|
73 | c |
---|
74 | c Local variables : |
---|
75 | c ----------------- |
---|
76 | INTEGER l,ig, n, nstep,i |
---|
77 | REAL co2heat0, zmu(ngrid) |
---|
78 | |
---|
79 | c special diurnal=F |
---|
80 | real mu0_int(ngrid),fract_int(ngrid),zday_int |
---|
81 | real ztim1,ztim2,ztim3,step |
---|
82 | |
---|
83 | c |
---|
84 | c local saved variables |
---|
85 | c --------------------- |
---|
86 | logical,save :: firstcall=.true. |
---|
87 | integer,save :: ico2=0 ! index of "co2" tracer |
---|
88 | integer,save :: io=0 ! index of "o" tracer |
---|
89 | |
---|
90 | !$OMP THREADPRIVATE(firstcall,ico2,io) |
---|
91 | |
---|
92 | c p0noonlte is a pressure below which non LTE effects are significant. |
---|
93 | c REAL p0nonlte |
---|
94 | c DATA p0nonlte/7.5e-3/ |
---|
95 | c SAVE p0nonlte |
---|
96 | |
---|
97 | c parameters for CO2 heating fit |
---|
98 | real,parameter :: n_a=1.1956475 |
---|
99 | real,parameter :: n_p0=0.0015888279 |
---|
100 | real,parameter :: n_b=1.9628251 |
---|
101 | |
---|
102 | c Variables added to implement NLTE correction factor (feb 2011) |
---|
103 | real pyy(nlayer) |
---|
104 | real cor1(nlayer),oldoco2(nlayer),alfa2(nlayer) |
---|
105 | real p2011,cociente1,merge |
---|
106 | real cor0,oco2gcm |
---|
107 | |
---|
108 | c---------------------------------------------------------------------- |
---|
109 | |
---|
110 | c Initialisation |
---|
111 | c -------------- |
---|
112 | ! AS: OK firstcall absolute |
---|
113 | if (firstcall) then |
---|
114 | if (nircorr.eq.1) then |
---|
115 | ! we will need co2 and o tracers |
---|
116 | ico2=igcm_co2 |
---|
117 | if (ico2==0) then |
---|
118 | write(*,*) "nirco2abs error: I need a CO2 tracer" |
---|
119 | write(*,*) " when running with nircorr==1" |
---|
120 | call abort_physic("nirco2abs","need a CO2 tracer",1) |
---|
121 | endif |
---|
122 | io=igcm_o |
---|
123 | if (io==0) then |
---|
124 | write(*,*) "nirco2abs error: I need an O tracer" |
---|
125 | write(*,*) " when running with nircorr==1" |
---|
126 | call abort_physic("nirco2abs","need an O tracer",1) |
---|
127 | endif |
---|
128 | endif |
---|
129 | firstcall=.false. |
---|
130 | endif |
---|
131 | |
---|
132 | |
---|
133 | c co2heat is the heating by CO2 at 700Pa for a zero zenithal angle. |
---|
134 | co2heat0=n_a*(1.52/dist_sol)**2/daysec |
---|
135 | |
---|
136 | c Simple calcul for a given sun incident angle (if diurnal=T) |
---|
137 | c -------------------------------------------- |
---|
138 | |
---|
139 | IF (diurnal) THEN |
---|
140 | do ig=1,ngrid |
---|
141 | zmu(ig)=sqrt(1224.*mu0(ig)*mu0(ig)+1.)/35. |
---|
142 | |
---|
143 | if(nircorr.eq.1) then |
---|
144 | do l=1,nlayer |
---|
145 | pyy(l)=pplay(ig,l) |
---|
146 | enddo |
---|
147 | |
---|
148 | call interpnir(cor1,pyy,nlayer,corgcm,pres1d,npres) |
---|
149 | call interpnir(oldoco2,pyy,nlayer,oco21d,pres1d,npres) |
---|
150 | call interpnir(alfa2,pyy,nlayer,alfa,pres1d,npres) |
---|
151 | endif |
---|
152 | |
---|
153 | do l=1,nlayer |
---|
154 | ! Calculations for the O/CO2 correction |
---|
155 | if(nircorr.eq.1) then |
---|
156 | cor0=1./(1.+n_p0/pplay(ig,l))**n_b |
---|
157 | if(pq(ig,l,ico2).gt.1.e-6) then |
---|
158 | oco2gcm=pq(ig,l,io)/pq(ig,l,ico2) |
---|
159 | ! handle the rare cases when pq(ig,l,io)<0 |
---|
160 | if (pq(ig,l,io).lt.0) then |
---|
161 | write(*,*) "nirco2abs: warning ig=",ig," l=",l, |
---|
162 | & " pq(ig,l,io)=",pq(ig,l,io) |
---|
163 | oco2gcm=1.e6 |
---|
164 | endif |
---|
165 | else |
---|
166 | oco2gcm=1.e6 |
---|
167 | endif |
---|
168 | cociente1=oco2gcm/oldoco2(l) |
---|
169 | merge=alog10(cociente1)*alfa2(l)+alog10(cor0)* |
---|
170 | $ (1.-alfa2(l)) |
---|
171 | merge=10**merge |
---|
172 | p2011=sqrt(merge)*cor0 |
---|
173 | else if (nircorr.eq.0) then |
---|
174 | p2011=1. |
---|
175 | cor1(l)=1. |
---|
176 | endif |
---|
177 | |
---|
178 | if(fract(ig).gt.0.) pdtnirco2(ig,l)= |
---|
179 | & co2heat0*sqrt((700.*zmu(ig))/pplay(ig,l)) |
---|
180 | & /(1.+n_p0/pplay(ig,l))**n_b |
---|
181 | ! Corrections from tabulation |
---|
182 | $ * cor1(l) * p2011 |
---|
183 | c OLD SCHEME (forget et al. 1999) |
---|
184 | c s co2heat0*sqrt((700.*zmu(ig))/pplay(ig,l)) |
---|
185 | c s / (1+p0nonlte/pplay(ig,l)) |
---|
186 | enddo |
---|
187 | enddo |
---|
188 | |
---|
189 | |
---|
190 | c Averaging over diurnal cycle (if diurnal=F) |
---|
191 | c ------------------------------------------- |
---|
192 | c NIR CO2 abs is slightly non linear. To remove the diurnal |
---|
193 | c cycle, it is better to average the heating rate over 1 day rather |
---|
194 | c than using the mean mu0 computed by mucorr in physiq.F (FF, 1998) |
---|
195 | |
---|
196 | ELSE ! if (.not.diurnal) then |
---|
197 | |
---|
198 | nstep = 20 ! number of integration step /sol |
---|
199 | mu0_int(1:ngrid) = 0. |
---|
200 | ztim1 = 0. |
---|
201 | do n=1,nstep |
---|
202 | zday_int = (n-1)/float(nstep) |
---|
203 | ztim2=COS(declin)*COS(2.*pi*(zday_int-.5)) |
---|
204 | ztim3=-COS(declin)*SIN(2.*pi*(zday_int-.5)) |
---|
205 | CALL solang(ngrid,sinlon,coslon,sinlat,coslat, |
---|
206 | s ztim1,ztim2,ztim3, |
---|
207 | s mu0_int,fract_int) |
---|
208 | do ig=1,ngrid |
---|
209 | zmu(ig)=sqrt(1224.*mu0_int(ig)*mu0_int(ig)+1.)/35. |
---|
210 | |
---|
211 | if(nircorr.eq.1) then |
---|
212 | do l=1,nlayer |
---|
213 | pyy(l)=pplay(ig,l) |
---|
214 | enddo |
---|
215 | call interpnir(cor1,pyy,nlayer,corgcm,pres1d,npres) |
---|
216 | call interpnir(oldoco2,pyy,nlayer,oco21d,pres1d,npres) |
---|
217 | call interpnir(alfa2,pyy,nlayer,alfa,pres1d,npres) |
---|
218 | endif |
---|
219 | |
---|
220 | do l=1,nlayer |
---|
221 | if(nircorr.eq.1) then |
---|
222 | cor0=1./(1.+n_p0/pplay(ig,l))**n_b |
---|
223 | oco2gcm=pq(ig,l,io)/pq(ig,l,ico2) |
---|
224 | cociente1=oco2gcm/oldoco2(l) |
---|
225 | merge=alog10(cociente1)*alfa2(l)+alog10(cor0)* |
---|
226 | $ (1.-alfa2(l)) |
---|
227 | merge=10**merge |
---|
228 | p2011=sqrt(merge)*cor0 |
---|
229 | else if (nircorr.eq.0) then |
---|
230 | p2011=1. |
---|
231 | cor1(l)=1. |
---|
232 | endif |
---|
233 | |
---|
234 | if(fract_int(ig).gt.0.) pdtnirco2(ig,l)= |
---|
235 | & pdtnirco2(ig,l) + (1/float(nstep))* |
---|
236 | & co2heat0*sqrt((700.*zmu(ig))/pplay(ig,l)) |
---|
237 | & /(1.+n_p0/pplay(ig,l))**n_b |
---|
238 | ! Corrections from tabulation |
---|
239 | $ * cor1(l) * p2011 |
---|
240 | enddo |
---|
241 | enddo |
---|
242 | end do |
---|
243 | END IF |
---|
244 | |
---|
245 | END SUBROUTINE nirco2abs |
---|
246 | |
---|
247 | |
---|
248 | |
---|
249 | subroutine interpnir(escout,p,nlayer,escin,pin,nl) |
---|
250 | C |
---|
251 | C subroutine to perform linear interpolation in pressure from 1D profile |
---|
252 | C escin(nl) sampled on pressure grid pin(nl) to profile |
---|
253 | C escout(nlayer) on pressure grid p(nlayer). |
---|
254 | C |
---|
255 | real,intent(out) :: escout(nlayer) |
---|
256 | real,intent(in) :: p(nlayer) |
---|
257 | integer,intent(in) :: nlayer |
---|
258 | real,intent(in) :: escin(nl) |
---|
259 | real,intent(in) :: pin(nl) |
---|
260 | integer,intent(in) :: nl |
---|
261 | |
---|
262 | real :: wm,wp |
---|
263 | integer :: n1,n,nm,np |
---|
264 | |
---|
265 | do n1=1,nlayer |
---|
266 | if(p(n1) .gt. 1500. .or. p(n1) .lt. 1.0e-13) then |
---|
267 | escout(n1) = 0.0 |
---|
268 | else |
---|
269 | do n = 1,nl-1 |
---|
270 | if (p(n1).le.pin(n).and.p(n1).ge.pin(n+1)) then |
---|
271 | nm=n |
---|
272 | np=n+1 |
---|
273 | wm=abs(pin(np)-p(n1))/(pin(nm)-pin(np)) |
---|
274 | wp=1.0 - wm |
---|
275 | endif |
---|
276 | enddo |
---|
277 | escout(n1) = escin(nm)*wm + escin(np)*wp |
---|
278 | endif |
---|
279 | enddo |
---|
280 | |
---|
281 | end subroutine interpnir |
---|
282 | |
---|
283 | END MODULE nirco2abs_mod |
---|