source: trunk/LMDZ.VENUS/libf/phyvenus/nirco2abs.F @ 1396

Last change on this file since 1396 was 1310, checked in by slebonnois, 11 years ago

SL: VENUS VERTICAL EXTENSION. NLTE and thermospheric processes, to be run with 78 levels and specific inputs.

File size: 9.1 KB
Line 
1      SUBROUTINE nirco2abs(nlon,nlev,nplay,dist_sol,nq,pq,
2     $     mu0,fract,pdtnirco2,
3     $     co2vmr_gcm, ovmr_gcm)
4
5       use dimphy
6       use comgeomphy, only: rlatd, rlond     
7c       use compo_hedin83_mod2
8
9
10       IMPLICIT NONE
11c=======================================================================
12c   subject:
13c   --------
14c   Computing heating rate due to
15c   absorption by CO2 in the near-infrared
16c   This version includes NLTE effects
17c
18c   (Scheme to be described in Forget et al., JGR, 2003)
19c   (old Scheme described in Forget et al., JGR, 1999)
20c
21c   This version updated with a new functional fit,
22c   see NLTE correction-factor of Lopez-Valverde et al (1998)
23c   Stephen Lewis 2000
24c
25C   jan 2014 g.gilli     
26C   jun 2013 l.salmi     First adaptation to Venus and NIR NLTE param
27c   jul 2011 malv+fgg    New corrections for NLTE implemented
28c   08/2002 : correction for bug when running with diurnal=F
29c
30c   author:  Frederic Hourdin 1996
31c   ------
32c            Francois Forget 1999
33c
34c   input:
35c   -----
36c   nlon                 number of gridpoint of horizontal grid
37c   nlev                Number of layer
38c   dist_sol              sun-Venus distance (AU)
39c   mu0(nlon)         
40c   fract(nlon)        day fraction of the time interval
41c   declin                latitude of subslar point
42c
43c   output:
44c   -------
45c
46c   pdtnirco2(nlon,nlev)      Heating rate (K/sec)
47c
48c
49c=======================================================================
50c
51c    0.  Declarations :
52c    ------------------
53c
54
55!#include "dimensions.h"
56#include "YOMCST.h"
57#include "clesphys.h"
58c#include "comdiurn.h"
59#include "nirdata.h"
60c#include "tracer.h"
61
62c-----------------------------------------------------------------------
63c    Input/Output
64c    ------------
65      integer,intent(in) :: nlon ! number of (horizontal) grid points
66     
67      integer,intent(in) :: nlev ! number of atmospheric layers
68      real,intent(in) :: nplay(nlon,nlev) ! Pressure
69      real,intent(in) :: dist_sol ! Sun-Venus distance (in AU)
70      integer,intent(in) :: nq ! number of tracers
71      real,intent(in) :: pq(nlon,nlev,nq) ! tracers
72      real,intent(in) :: mu0(nlon) ! solar angle
73      real,intent(in) :: fract(nlon) ! day fraction of the time interval
74c      real,intent(in) :: declin ! latitude of sub-solar point
75
76      real co2vmr_gcm(nlon,nlev),ovmr_gcm(nlon,nlev)
77
78      real,intent(out) :: pdtnirco2(nlon,nlev) ! heating rate (K/sec)
79
80c
81c    Local variables :
82c    -----------------
83      INTEGER l,ig, n, nstep,i
84      REAL co2heat0, zmu(nlon)
85
86c     special diurnal=F
87      real mu0_int(nlon),fract_int(nlon),zday_int
88      real ztim1,ztim2,ztim3,step
89
90c
91c   local saved variables
92c   ---------------------
93      logical,save :: firstcall=.true.
94      integer,save :: ico2=0 ! index of "co2" tracer
95      integer,save :: io=0 ! index of "o" tracer
96
97ccc
98c
99c     n_a  =  heating rate for Venusian day at p0, r0, mu =0 [K day-1]
100c     Here p0 = p_cloud top [Pa]
101c     n_p0 = is a pressure below which non LTE effects are significant [Pa]
102c     n_a Solar heating [K/Eday] at the cloud top, taken from Crisps table     
103 
104      real n_a, n_p0, n_b, p_ctop
105
106cc Current values
107       parameter (n_a = 18.13/86400.0)    !!     K/Eday  ---> K/sec   
108       parameter (p_ctop=13.2e2)
109
110c    -- NLTE Param v2  --
111c       parameter (n_p0=0.01) 
112c       parameter (n_b = 1.3)
113 
114ccc TESTS 
115c       parameter (n_a = 18.4/86400.0 *0.6) 
116c       parameter (p_ctop=63.9e2)
117c       parameter (n_p0=0.012)
118c       parameter (n_b=1.9628251)
119
120
121c    -- NLTE Param v1  --
122c       parameter (n_p0=0.012)   
123c       parameter (n_b = 1.4)
124
125c    -- NLTE Param v3  --
126
127       parameter (n_p0=0.008)   
128       parameter (n_b = 1.362)
129
130
131c     Variables added to implement NLTE correction factor (feb 2011)
132      real    pyy(nlev)
133      real    cor1(nlev),oldoco2(nlev),alfa2(nlev)
134      real    p2011,cociente1,merge
135      real    cor0,oco2gcm
136
137c     co2heat is the heating by CO2 at p_ctop=9.3E03 Pa (cloud top 65 km) for a zero zenithal angle.
138
139      co2heat0=n_a*(0.72/dist_sol)**2     
140
141
142CCCCCC   TEST: reduce/incrise by 50% nir Heating
143
144c      co2heat0  = co2heat0 * 2
145
146
147c----------------------------------------------------------------------
148     
149c     Initialisation
150c     --------------
151c      if (firstcall) then
152c        if (nircorr.eq.1) then
153cc          ! we will need co2 and o tracers
154c          ico2= igcm_co2
155c          if (ico2==0) then
156c            write(*,*) "nirco2abs error: I need a CO2 tracer"
157c            write(*,*) "     when running with nircorr==1"
158c           stop
159c          endif
160c          io=igcm_o
161c          if (io==0) then
162c            write(*,*) "nirco2abs error: I need an O tracer"
163c            write(*,*) "     when running with nircorr==1"
164c            stop
165c          endif
166c        endif
167c        firstcall=.false.
168c      endif
169
170     
171c     
172c     Simple calcul for a given sun incident angle (if cycle_diurne=T)
173c     --------------------------------------------
174
175      IF (cycle_diurne) THEN 
176
177         do ig=1,nlon   
178            zmu(ig)=sqrt(1224.*mu0(ig)*mu0(ig)+1.)/35.
179
180           
181            if(nircorr.eq.1) then
182               do l=1,nlev
183                  pyy(l)=nplay(ig,l)
184               enddo
185
186               call interpnir(cor1,pyy,nlev,corgcm,pres1d,npres)
187               call interpnir(oldoco2,pyy,nlev,oco21d,pres1d,npres)
188               call interpnir(alfa2,pyy,nlev,alfa,pres1d,npres)
189
190            endif
191
192            do l=1,nlev
193c           Calculations for the O/CO2 correction
194               if(nircorr.eq.1) then
195                  cor0=1./(1.+n_p0/nplay(ig,l))**n_b
196                  if(co2vmr_gcm(ig,l).gt.1.e-6) then
197                     oco2gcm=ovmr_gcm(ig,l)/co2vmr_gcm(ig,l)
198                  else
199                     oco2gcm=1.e6
200                  endif
201                  cociente1=oco2gcm/oldoco2(l)
202                  merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
203     $                 (1.-alfa2(l))
204                  merge=10**merge
205                  p2011=sqrt(merge)*cor0
206
207               else if (nircorr.eq.0) then
208                  p2011=1.
209                  cor1(l)=1.
210               endif
211
212
213              if(fract(ig).gt.0.) pdtnirco2(ig,l)=
214     &             co2heat0*sqrt((p_ctop*zmu(ig))/nplay(ig,l))
215     &             /(1.+n_p0/nplay(ig,l))**n_b
216c           Corrections from tabulation
217     $              * cor1(l) * p2011
218
219
220          enddo
221         enddo
222         
223c     Averaging over diurnal cycle (if diurnal=F)
224c     -------------------------------------------
225c     NIR CO2 abs is slightly non linear. To remove the diurnal
226c     cycle, it is better to average the heating rate over 1 day rather
227c     than using the mean mu0 computed by mucorr in physiq.F (FF, 1998)
228
229      ELSE      ! if (.not.diurnal) then
230         nstep = 20    ! number of integration step /sol
231         do n=1,nstep
232
233            zday_int = (n-1)/float(nstep)
234
235            CALL zenang(0.,zday_int,RDAY/nstep,rlatd,rlond,
236     s             mu0_int,fract_int)
237
238            do ig=1,nlon
239               zmu(ig)=sqrt(1224.*mu0_int(ig)*mu0_int(ig)+1.)/35.
240
241               if(nircorr.eq.1) then
242                  do l=1,nlev
243                     pyy(l)=nplay(ig,l)
244                  enddo
245                 call interpnir(cor1,pyy,nlev,corgcm,pres1d,npres)
246                 call interpnir(oldoco2,pyy,nlev,oco21d,pres1d,npres)
247                 call interpnir(alfa2,pyy,nlev,alfa,pres1d,npres)
248               endif
249c
250
251               do l=1,nlev
252                  if(nircorr.eq.1) then
253                      cor0=1./(1.+n_p0/nplay(ig,l))**n_b
254c                     oco2gcm=ovmr_gcm(ig,l)/co2vmr_gcm(ig,l)
255                     cociente1 = 1
256                     merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
257     $                    (1.-alfa2(l))
258                     merge=10**merge
259                     p2011=sqrt(merge)*cor0
260                  else if (nircorr.eq.0) then
261                     p2011=1.
262                     cor1(l)=1.
263                  endif
264
265c
266
267                  if(fract_int(ig).gt.0.) pdtnirco2(ig,l)=
268     &                 pdtnirco2(ig,l) + (1/float(nstep))*
269     &                 co2heat0*sqrt((p_ctop*zmu(ig))/nplay(ig,l))
270     &                 /(1.+n_p0/nplay(ig,l))**n_b
271!                      Corrections from tabulation
272     $                 * cor1(l) * p2011
273
274               enddo
275            enddo
276         end do
277     
278      END IF
279
280      return
281      end
282
283
284     
285      subroutine interpnir(escout,p,nlev,escin,pin,nl)
286C
287C subroutine to perform linear interpolation in pressure from 1D profile
288C escin(nl) sampled on pressure grid pin(nl) to profile
289C escout(nlev) on pressure grid p(nlev).
290C
291      real escout(nlev),p(nlev)
292      real escin(nl),pin(nl),wm,wp
293      integer nl,nlev,n1,n,nm,np
294      do n1=1,nlev
295         if(p(n1) .gt. 1500. .or. p(n1) .lt. 1.0e-13) then
296            escout(n1) = 0.0
297         else
298            do n = 1,nl-1
299               if (p(n1).le.pin(n).and.p(n1).ge.pin(n+1)) then
300                  nm=n
301                  np=n+1
302                  wm=abs(pin(np)-p(n1))/(pin(nm)-pin(np))
303                  wp=1.0 - wm
304               endif
305            enddo
306            escout(n1) = escin(nm)*wm + escin(np)*wp
307         endif
308      enddo
309      return
310      end
Note: See TracBrowser for help on using the repository browser.