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

Last change on this file since 1453 was 1442, checked in by slebonnois, 9 years ago

SL: update of the Venus GCM, + corrections on routines used for newstart/start2archive for Titan and Venus, + some modifications on tools

File size: 9.4 KB
Line 
1      SUBROUTINE nirco2abs(nlon,nlev,nplay,dist_sol,nq,pq,
2     $     mu0,fract,pdtnirco2)
3
4       use dimphy
5       use comgeomphy, only: rlatd, rlond     
6       use chemparam_mod, only: i_co2, i_o
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   oct 2014 g.gilli     Coupling with photochemical model
26C   jan 2014 g.gilli     Revision (following martian non-lte param)   
27C   jun 2013 l.salmi     First adaptation to Venus and NIR NLTE param
28c   jul 2011 malv+fgg    New corrections for NLTE implemented
29c   08/2002 : correction for bug when running with diurnal=F
30c
31c   author:  Frederic Hourdin 1996
32c   ------
33c            Francois Forget 1999
34c
35c   input:
36c   -----
37c   nlon                 number of gridpoint of horizontal grid
38c   nlev                Number of layer
39c   dist_sol              sun-Venus distance (AU)
40c   mu0(nlon)         
41c   fract(nlon)        day fraction of the time interval
42c   declin                latitude of subslar point
43c
44c   output:
45c   -------
46c
47c   pdtnirco2(nlon,nlev)      Heating rate (K/sec)
48c
49c
50c=======================================================================
51c
52c    0.  Declarations :
53c    ------------------
54c
55
56!#include "dimensions.h"
57#include "YOMCST.h"
58#include "clesphys.h"
59c#include "comdiurn.h"
60#include "nirdata.h"
61c#include "tracer.h"
62#include "mmol.h"
63c-----------------------------------------------------------------------
64c    Input/Output
65c    ------------
66      integer,intent(in) :: nlon ! number of (horizontal) grid points
67      integer,intent(in) :: nlev ! number of atmospheric layers
68
69      real,intent(in) :: nplay(nlon,nlev) ! Pressure
70      real,intent(in) :: dist_sol ! Sun-Venus distance (in AU)
71      integer,intent(in) :: nq ! number of tracers
72      real,intent(in) :: pq(nlon,nlev,nq) ! mass mixing ratio tracers
73      real,intent(in) :: mu0(nlon) ! solar angle
74      real,intent(in) :: fract(nlon) ! day fraction of the time interval
75c      real,intent(in) :: declin ! latitude of sub-solar point
76      real :: co2vmr_gcm(nlon,nlev), o3pvmr_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
97cccc     parameters for CO2 heating fit
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
106   
107cc "Nominal" values
108       parameter (n_a = 18.13/86400.0)     !c     K/Eday  ---> K/sec   
109       parameter (p_ctop=13.2e2)
110c    -- NLTE Param v3  --
111       parameter (n_p0=0.008) 
112       parameter (n_b=1.362)
113
114cc   -- Varoxy5
115C       parameter (n_a = 20/86400.0)
116C       parameter (p_ctop=870)   ! [Pa]
117C       parameter (n_b=1.98)
118C       parameter (n_p0=0.045)
119
120c      parameter (n_p0=0.1) !!!!cccc test varoxy5mod
121c      parameter (n_b=0.9)
122
123
124c    -- NLTE Param v2  --
125C       parameter (n_p0=0.01) 
126c       parameter (n_b = 1.3)
127   
128
129
130c     Variables added to implement NLTE correction factor (feb 2011)
131      real    pyy(nlev)
132      real    cor1(nlev),oldoco2(nlev),alfa2(nlev)
133      real    p2011,cociente1,merge
134      real    cor0,oco2gcm
135!!!!
136c      real :: pic27(nlon,nlev), pic27b(nlon,nlev)
137c      real :: pic43(nlon,nlev), picnir(nlon,nlev)
138
139c     co2heat is the heating by CO2 at p_ctop=13.2e2 for a zero zenithal angle.
140
141      co2heat0=n_a*(0.72/dist_sol)**2     
142
143CCCCCC   TEST: reduce by X% nir Heating
144
145c      co2heat0  = co2heat0 * 0.8
146
147
148c----------------------------------------------------------------------
149     
150c     Initialisation
151c     --------------
152      if (firstcall) then
153        if (nircorr.eq.1) then
154c          ! we will need co2 and o tracers
155          ico2= i_co2
156          if (ico2==0) then
157            write(*,*) "nirco2abs error: I need a CO2 tracer"
158            write(*,*) "     when running with nircorr==1"
159           stop
160          endif
161          io=i_o
162          if (io==0) then
163            write(*,*) "nirco2abs error: I need an O tracer"
164            write(*,*) "     when running with nircorr==1"
165            stop
166          endif
167        endif
168        firstcall=.false.
169      endif
170
171     
172c     
173c     Simple calcul for a given sun incident angle (if cycle_diurne=T)
174c     --------------------------------------------
175
176      IF (cycle_diurne) THEN 
177
178         do ig=1,nlon   
179            zmu(ig)=sqrt(1224.*mu0(ig)*mu0(ig)+1.)/35.
180
181           
182            if(nircorr.eq.1) then
183               do l=1,nlev
184                  pyy(l)=nplay(ig,l)
185               enddo
186
187               call interpnir(cor1,pyy,nlev,corgcm,pres1d,npres)
188               call interpnir(oldoco2,pyy,nlev,oco21d,pres1d,npres)
189               call interpnir(alfa2,pyy,nlev,alfa,pres1d,npres)
190               
191            endif
192
193            do l=1,nlev
194     
195c           Calculations for the O/CO2 correction
196               if(nircorr.eq.1) then
197                  cor0=1./(1.+n_p0/nplay(ig,l))**n_b
198                  if(pq(ig,l,ico2) .gt. 1.e-6) then
199                     oco2gcm=pq(ig,l,io)/pq(ig,l,ico2)
200
201                  else
202                     oco2gcm=1.e6
203                  endif
204                  cociente1=oco2gcm/oldoco2(l)
205                 
206c                  WRITE(*,*) "nirco2abs line 211", l, cociente1
207
208                  merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
209     $                 (1.-alfa2(l))
210                  merge=10**merge
211                  p2011=sqrt(merge)*cor0
212
213               else if (nircorr.eq.0) then
214                  p2011=1.
215                  cor1(l)=1.
216               endif
217
218              if(fract(ig).gt.0.) pdtnirco2(ig,l)=
219     &             co2heat0*sqrt((p_ctop*zmu(ig))/nplay(ig,l))
220     &             /(1.+n_p0/nplay(ig,l))**n_b
221c           Corrections from tabulation
222     $              * cor1(l) * p2011
223             
224          enddo
225         enddo
226         
227c     Averaging over diurnal cycle (if diurnal=F)
228c     -------------------------------------------
229c     NIR CO2 abs is slightly non linear. To remove the diurnal
230c     cycle, it is better to average the heating rate over 1 day rather
231c     than using the mean mu0 computed by mucorr in physiq.F (FF, 1998)
232
233      ELSE      ! if (.not.diurnal) then
234         nstep = 20    ! number of integration step /sol
235         do n=1,nstep
236
237            zday_int = (n-1)/float(nstep)
238
239            CALL zenang(0.,zday_int,RDAY/nstep,rlatd,rlond,
240     s             mu0_int,fract_int)
241
242            do ig=1,nlon
243               zmu(ig)=sqrt(1224.*mu0_int(ig)*mu0_int(ig)+1.)/35.
244
245               if(nircorr.eq.1) then
246                  do l=1,nlev
247                     pyy(l)=nplay(ig,l)
248                  enddo
249                 call interpnir(cor1,pyy,nlev,corgcm,pres1d,npres)
250                 call interpnir(oldoco2,pyy,nlev,oco21d,pres1d,npres)
251                 call interpnir(alfa2,pyy,nlev,alfa,pres1d,npres)
252               endif
253c
254
255               do l=1,nlev
256c           Calculations for the O/CO2 correction
257               if(nircorr.eq.1) then
258                  cor0=1./(1.+n_p0/nplay(ig,l))**n_b
259                  oco2gcm=pq(ig,l,io)/pq(ig,l,ico2)
260                  cociente1=oco2gcm/oldoco2(l)
261                  merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
262     $                 (1.-alfa2(l))
263                  merge=10**merge
264                  p2011=sqrt(merge)*cor0
265
266               else if (nircorr.eq.0) then
267                  p2011=1.
268                  cor1(l)=1.
269               endif
270
271               if(fract_int(ig).gt.0.) pdtnirco2(ig,l)=
272     &              pdtnirco2(ig,l) + (1/float(nstep))*
273     &              co2heat0*sqrt((p_ctop*zmu(ig))/nplay(ig,l))
274     &              /(1.+n_p0/nplay(ig,l))**n_b
275!     Corrections from tabulation
276     $              * cor1(l) * p2011
277
278               enddo
279            enddo
280         end do
281     
282
283      END IF 
284
285      return
286      end
287
288     
289      subroutine interpnir(escout,p,nlev,escin,pin,nl)
290C
291C subroutine to perform linear interpolation in pressure from 1D profile
292C escin(nl) sampled on pressure grid pin(nl) to profile
293C escout(nlev) on pressure grid p(nlev).
294C
295      real escout(nlev),p(nlev)
296      real escin(nl),pin(nl),wm,wp
297      integer nl,nlev,n1,n,nm,np
298      do n1=1,nlev
299         if(p(n1) .gt. 1500. .or. p(n1) .lt. 1.0e-13) then
300c            escout(n1) = 0.0
301            escout(n1) = 1.e-15
302         else
303            do n = 1,nl-1
304               if (p(n1).le.pin(n).and.p(n1).ge.pin(n+1)) then
305                  nm=n
306                  np=n+1
307                  wm=abs(pin(np)-p(n1))/(pin(nm)-pin(np))
308                  wp=1.0 - wm
309               endif
310            enddo
311            escout(n1) = escin(nm)*wm + escin(np)*wp
312         endif
313      enddo
314      return
315      end
Note: See TracBrowser for help on using the repository browser.