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

Last change on this file since 3884 was 3884, checked in by ikovalenko, 4 months ago
File size: 15.7 KB
Line 
1      SUBROUTINE nirco2abs(nlon,nlev,nplay,dist_sol,nq,pq,
2     $     mu0,fract,pdtnirco2)
3
4       use dimphy
5       use geometry_mod, only: longitude_deg, latitude_deg
6       use chemparam_mod, only: i_co2, i_o
7       use mmol_mod
8       use clesphys_mod
9       use YOMCST_mod
10c       use compo_hedin83_mod2
11
12
13       IMPLICIT NONE
14c=======================================================================
15c   subject:
16c   --------
17c   Computing heating rate due to
18c   absorption by CO2 in the near-infrared
19c   This version includes NLTE effects
20c
21c   (Scheme to be described in Forget et al., JGR, 2003)
22c   (old Scheme described in Forget et al., JGR, 1999)
23c
24c   This version updated with a new functional fit,
25c   see NLTE correction-factor of Lopez-Valverde et al (1998)
26c   Stephen Lewis 2000
27c
28c   apr 2019 d.quirino   Improving NLTE params, SOIR/SPICAV Temp comparison
29c   oct 2014 g.gilli     Coupling with photochemical model
30C   jan 2014 g.gilli     Revision (following martian non-lte param)   
31C   jun 2013 l.salmi     First adaptation to Venus and NIR NLTE param
32c   jul 2011 malv+fgg    New corrections for NLTE implemented
33c   08/2002 : correction for bug when running with diurnal=F
34c
35c   author:  Frederic Hourdin 1996
36c   ------
37c            Francois Forget 1999
38c
39c   input:
40c   -----
41c   nlon                 number of gridpoint of horizontal grid
42c   nlev                Number of layer
43c   dist_sol              sun-Venus distance (AU)
44c   mu0(nlon)         
45c   fract(nlon)        day fraction of the time interval
46c   declin                latitude of subslar point
47c
48c   output:
49c   -------
50c
51c   pdtnirco2(nlon,nlev)      Heating rate (K/sec)
52c
53c
54c=======================================================================
55c
56c    0.  Declarations :
57c    ------------------
58c
59
60c#include "YOMCST.h"
61c#include "clesphys.h"
62c#include "comdiurn.h"
63#include "nirdata.h"
64c#include "tracer.h"
65c#include "mmol.h"
66
67c-----------------------------------------------------------------------
68c    Input/Output
69c    ------------
70      integer,intent(in) :: nlon ! number of (horizontal) grid points
71      integer,intent(in) :: nlev ! number of atmospheric layers
72
73      real,intent(in) :: nplay(nlon,nlev) ! Pressure
74      real,intent(in) :: dist_sol ! Sun-Venus distance (in AU)
75      integer,intent(in) :: nq ! number of tracers
76      real,intent(in) :: pq(nlon,nlev,nq) ! mass mixing ratio tracers
77      real,intent(in) :: mu0(nlon) ! solar angle
78      real,intent(in) :: fract(nlon) ! day fraction of the time interval
79c      real,intent(in) :: declin ! latitude of sub-solar point
80      real :: co2vmr_gcm(nlon,nlev), o3pvmr_gcm(nlon,nlev)
81 
82      real,intent(out) :: pdtnirco2(nlon,nlev) ! heating rate (K/sec)
83
84c
85c    Local variables :
86c    -----------------
87      INTEGER l,ig, n, nstep,i
88      REAL co2heat0, zmu(nlon)
89
90c     special diurnal=F
91      real mu0_int(nlon),fract_int(nlon),zday_int
92      real ztim1,ztim2,ztim3,step
93
94      logical onepeak
95      parameter (onepeak=.false.)
96c     parameter (onepeak=.true.)
97c
98c   local saved variables
99c   ---------------------
100      logical,save :: firstcall=.true.
101      integer,save :: ico2=0 ! index of "co2" tracer
102      integer,save :: io=0 ! index of "o" tracer
103
104ccc=================================================
105cccc     parameters for CO2 heating fit
106ccc=================================================
107
108c--------------------------------------------------
109c One-peak martian-type fit => Gabriella (2014+)
110c--------------------------------------------------
111c     n_a  =  heating rate for Venusian day at p0, r0, mu =0 [K day-1]
112c     Here p0 = p_cloud top [Pa]
113c     n_p0 = is a pressure below which non LTE effects are significant [Pa]
114c     n_a Solar heating [K/Eday] at the cloud top, taken from Crisps table     
115 
116      real n_a, n_p0, n_b, p_ctop
117
118cc "Nominal" values used in Gilli+2017
119c       parameter (n_a = 18.13/86400.0)     !c     K/Eday  ---> K/sec   
120c       parameter (p_ctop=13.2e2)
121c       parameter (n_p0=0.008)
122
123cc "New" values used to improve SPICAV/SOIR Temperature comparision (D.Quirino)
124cc Gilli+2021
125       parameter (n_a = 15.92/86400.0)     !c     K/Eday  ---> K/sec   
126       parameter (p_ctop=19.85e2)
127       parameter (n_p0=0.1) 
128       parameter (n_b=1.362)
129
130c    -- NLTE Param v2  --
131C       parameter (n_p0=0.01) 
132c       parameter (n_b = 1.3)
133
134c--------------------------------------------------
135c Multi-peaks Roldan-type fit => Laura (2013)
136c New paramaters (Param9*0.5) => Enora (2021)
137c--------------------------------------------------
138c ENORA FINE TUNING used for VCD 1.1
139c  (fit to fig 12 Roldan-2000)
140      real n_coFB, n_aFB, n_bFB, n_p0FB, n_eFB
141      real n_coISO, n_aISO, n_bISO, n_p0ISO, n_eISO
142      real n_coFH, n_aFH, n_bFH, n_p0FH, n_eFH
143      real n_co43, n_a43, n_b43, n_p043, n_e43
144      real n_co43b, n_a43b, n_b43b, n_p043b, n_e43b
145      real n_conir, n_anir, n_bnir, n_p0nir, n_enir
146
147      parameter (n_coFB=119./86400.0)      !c     K/Eday ---> K/sec
148      parameter (n_aFB=0.185)
149      parameter (n_bFB=3.7)
150      parameter (n_p0FB=2.9e-4)
151      parameter (n_eFB=0.76)
152
153      parameter (n_coISO=265./86400.0)      !c     K/Eday ---> K/sec
154      parameter (n_aISO=0.313)
155      parameter (n_bISO=1.65)
156      parameter (n_p0ISO=0.076)
157      parameter (n_eISO=0.99)
158
159      parameter (n_coFH=2.5/86400.0)      !c     K/Eday ---> K/sec
160      parameter (n_aFH=3.98)
161      parameter (n_bFH=2.9)
162      parameter (n_p0FH=0.17)
163      parameter (n_eFH=2.16)
164
165      parameter (n_co43=55./86400.0)      !c     K/Eday ---> K/sec
166      parameter (n_a43=0.625)
167      parameter (n_b43=2.6)
168      parameter (n_p043=0.043)
169      parameter (n_e43=1.654)
170
171!     parameter (n_co43b=100./86400.0)      !c     K/Eday ---> K/sec
172! => fine tuning: not affected by the *0.5 below (see ENORA FINE TUNING)
173      parameter (n_co43b=200./86400.0)      !c     K/Eday ---> K/sec
174      parameter (n_a43b=5.5)
175      parameter (n_b43b=2.3)
176      parameter (n_p043b=1.)
177      parameter (n_e43b=0.4)
178
179      parameter (n_conir=6.5/86400.0)      !c     K/Eday ---> K/sec
180      parameter (n_anir=35.65)
181      parameter (n_bnir=2.1)
182      parameter (n_p0nir=0.046)
183      parameter (n_enir=0.9)
184
185      real :: picFB(nlon,nlev), picISO(nlon,nlev), picFH(nlon,nlev)
186      real :: pic43(nlon,nlev), pic43b(nlon,nlev), picnir(nlon,nlev)
187
188ccc=================================================
189
190c     Variables added to implement NLTE correction factor (feb 2011)
191      real    pyy(nlev)
192      real    cor1(nlev),oldoco2(nlev),alfa2(nlev)
193      real    p2011,cociente1,merge
194      real    cor0,oco2gcm
195
196c---------------------------------------------------------------------- 
197c     Initialisation
198c     --------------
199      if (firstcall) then
200        if (nircorr.eq.1) then
201c          ! we will need co2 and o tracers
202          ico2= i_co2
203          if (ico2==0) then
204            write(*,*) "nirco2abs error: I need a CO2 tracer"
205            write(*,*) "     when running with nircorr==1"
206           stop
207          endif
208          io=i_o
209          if (io==0) then
210            write(*,*) "nirco2abs error: I need an O tracer"
211            write(*,*) "     when running with nircorr==1"
212            stop
213          endif
214        endif
215        firstcall=.false.
216      endif
217c     --------------
218c     co2heat0 is correction for dist_sol (is 1 for Venus)
219      co2heat0=(0.7233/dist_sol)**2
220
221      pdtnirco2(:,:)=0.
222c---------------------------------------------------------------------- 
223
224c     
225c     Simple calcul for a given sun incident angle (if cycle_diurne=T)
226c     --------------------------------------------
227
228      IF (cycle_diurne) THEN 
229
230         do ig=1,nlon   
231            zmu(ig)=sqrt(1224.*mu0(ig)*mu0(ig)+1.)/35.
232
233c---------------------------
234           if (onepeak) then
235c---------------------------
236            if(nircorr.eq.1) then
237               do l=1,nlev
238                  pyy(l)=nplay(ig,l)
239               enddo
240               call interpnir(cor1,pyy,nlev,corgcm,pres1d,npres)
241               call interpnir(oldoco2,pyy,nlev,oco21d,pres1d,npres)
242               call interpnir(alfa2,pyy,nlev,alfa,pres1d,npres)
243            endif
244            do l=1,nlev
245c           Calculations for the O/CO2 correction
246               if(nircorr.eq.1) then
247                  cor0=1./(1.+n_p0/nplay(ig,l))**n_b
248                  if(pq(ig,l,ico2) .gt. 1.e-6) then
249                     oco2gcm=pq(ig,l,io)/pq(ig,l,ico2)
250                     ! handle the rare cases when pq(ig,l,io)<0
251                     if (pq(ig,l,io).lt.0) then
252                       write(*,*) "nirco2abs: warning ig=",ig," l=",l,
253     &                            " pq(ig,l,io)=",pq(ig,l,io)
254                       oco2gcm=1.e6
255                     endif
256                  else
257                     oco2gcm=1.e6
258                  endif
259                  cociente1=oco2gcm/oldoco2(l)
260                 
261c                  WRITE(*,*) "nirco2abs line 211", l, cociente1
262
263                  merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
264     $                 (1.-alfa2(l))
265                  merge=10**merge
266                  p2011=sqrt(merge)*cor0
267
268               else if (nircorr.eq.0) then
269                  p2011=1.
270                  cor1(l)=1.
271               endif
272
273              if(fract(ig).gt.0.) pdtnirco2(ig,l)=
274     &             co2heat0*n_a*sqrt((p_ctop*zmu(ig))/nplay(ig,l))
275     &             /(1.+n_p0/nplay(ig,l))**n_b
276c           Corrections from tabulation
277     $              * cor1(l) * p2011
278             
279            enddo !nlev
280c---------------------------
281           else  ! multipeak
282c---------------------------
283            do l=1,nlev
284               if(fract(ig).gt.0.) then
285                   picFB(ig,l)=n_coFB
286     &              *((n_aFB/nplay(ig,l))**n_eFB)
287     &              *zmu(ig)**0.82
288     &             /(1.+n_p0FB/nplay(ig,l))**n_bFB
289
290                   picISO(ig,l)=n_coISO
291     &              *((n_aISO/nplay(ig,l))**n_eISO)
292     &              *zmu(ig)**0.55
293     &             /(1.+n_p0ISO/nplay(ig,l))**n_bISO
294
295                   picFH(ig,l)=n_coFH
296     &              *((n_aFH/nplay(ig,l))**n_eFH)
297     &              *zmu(ig)**0.55
298     &             /(1.+n_p0FH/nplay(ig,l))**n_bFH
299
300                   pic43(ig,l)=n_co43
301     &              *((n_a43/nplay(ig,l))**n_e43)
302     &              *zmu(ig)**0.55
303     &             /(1.+n_p043/nplay(ig,l))**n_b43
304
305                   pic43b(ig,l)=n_co43b
306     &              *((n_a43b/nplay(ig,l))**n_e43b)
307     &              *zmu(ig)**0.55
308     &             /(1.+n_p043b/nplay(ig,l))**n_b43b
309
310                   picnir(ig,l)=n_conir
311     &              *((n_anir/nplay(ig,l))**n_enir)
312     &              *zmu(ig)**0.55
313     &             /(1.+n_p0nir/nplay(ig,l))**n_bnir
314
315                   pdtnirco2(ig,l)=co2heat0*
316     &           (picFB(ig,l)+picISO(ig,l)+picFH(ig,l)+pic43(ig,l)
317     &           +pic43b(ig,l)+picnir(ig,l))*0.5  ! *0.5 = ENORA FINE TUNING
318                 
319               endif
320            enddo !nlev
321c---------------------------
322           endif
323c---------------------------
324         enddo  !nlon
325
326
327c     Averaging over diurnal cycle (if diurnal=F)
328c     -------------------------------------------
329c     NIR CO2 abs is slightly non linear. To remove the diurnal
330c     cycle, it is better to average the heating rate over 1 day rather
331c     than using the mean mu0 computed by mucorr in physiq.F (FF, 1998)
332
333      ELSE      ! if (.not.diurnal) then
334         nstep = 20    ! number of integration step /sol
335         do n=1,nstep
336
337            zday_int = (n-1)/float(nstep)
338
339            CALL zenang(0.,zday_int,RDAY/nstep,
340     &                  latitude_deg,longitude_deg,
341     &                  mu0_int,fract_int)
342
343          do ig=1,nlon
344               zmu(ig)=sqrt(1224.*mu0_int(ig)*mu0_int(ig)+1.)/35.
345
346c---------------------------
347           if (onepeak) then
348c---------------------------
349            if(nircorr.eq.1) then
350               do l=1,nlev
351                  pyy(l)=nplay(ig,l)
352               enddo
353               call interpnir(cor1,pyy,nlev,corgcm,pres1d,npres)
354               call interpnir(oldoco2,pyy,nlev,oco21d,pres1d,npres)
355               call interpnir(alfa2,pyy,nlev,alfa,pres1d,npres)
356            endif
357            do l=1,nlev
358c           Calculations for the O/CO2 correction
359               if(nircorr.eq.1) then
360                  cor0=1./(1.+n_p0/nplay(ig,l))**n_b
361                  if(pq(ig,l,ico2) .gt. 1.e-6) then
362                     oco2gcm=pq(ig,l,io)/pq(ig,l,ico2)
363                     ! handle the rare cases when pq(ig,l,io)<0
364                     if (pq(ig,l,io).lt.0) then
365                       write(*,*) "nirco2abs: warning ig=",ig," l=",l,
366     &                            " pq(ig,l,io)=",pq(ig,l,io)
367                       oco2gcm=1.e6
368                     endif
369                  else
370                     oco2gcm=1.e6
371                  endif
372                  cociente1=oco2gcm/oldoco2(l)
373                 
374c                  WRITE(*,*) "nirco2abs line 211", l, cociente1
375
376                  merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
377     $                 (1.-alfa2(l))
378                  merge=10**merge
379                  p2011=sqrt(merge)*cor0
380
381               else if (nircorr.eq.0) then
382                  p2011=1.
383                  cor1(l)=1.
384               endif
385
386              if(fract(ig).gt.0.) pdtnirco2(ig,l)=
387     &              pdtnirco2(ig,l) + (1/float(nstep))*
388     &             co2heat0*n_a*sqrt((p_ctop*zmu(ig))/nplay(ig,l))
389     &             /(1.+n_p0/nplay(ig,l))**n_b
390c           Corrections from tabulation
391     $              * cor1(l) * p2011
392             
393            enddo !nlev
394c---------------------------
395           else  ! multipeak
396c---------------------------
397            do l=1,nlev
398               if(fract(ig).gt.0.) then
399                   picFB(ig,l)=n_coFB
400     &              *((n_aFB/nplay(ig,l))**n_eFB)
401     &              *zmu(ig)**0.82
402     &             /(1.+n_p0FB/nplay(ig,l))**n_bFB
403
404                   picISO(ig,l)=n_coISO
405     &              *((n_aISO/nplay(ig,l))**n_eISO)
406     &              *zmu(ig)**0.55
407     &             /(1.+n_p0ISO/nplay(ig,l))**n_bISO
408
409                   picFH(ig,l)=n_coFH
410     &              *((n_aFH/nplay(ig,l))**n_eFH)
411     &              *zmu(ig)**0.55
412     &             /(1.+n_p0FH/nplay(ig,l))**n_bFH
413
414                   pic43(ig,l)=n_co43
415     &              *((n_a43/nplay(ig,l))**n_e43)
416     &              *zmu(ig)**0.55
417     &             /(1.+n_p043/nplay(ig,l))**n_b43
418
419                   pic43b(ig,l)=n_co43b
420     &              *((n_a43b/nplay(ig,l))**n_e43b)
421     &              *zmu(ig)**0.55
422     &             /(1.+n_p043b/nplay(ig,l))**n_b43b
423
424                   picnir(ig,l)=n_conir
425     &              *((n_anir/nplay(ig,l))**n_enir)
426     &              *zmu(ig)**0.55
427     &             /(1.+n_p0nir/nplay(ig,l))**n_bnir
428
429                   pdtnirco2(ig,l)=
430     &               pdtnirco2(ig,l)+(1/float(nstep))*co2heat0*
431     &           (picFB(ig,l)+picISO(ig,l)+picFH(ig,l)+pic43(ig,l)
432     &           +pic43b(ig,l)+picnir(ig,l))*0.5  ! *0.5 = ENORA FINE TUNING
433                 
434               endif
435            enddo !nlev
436c---------------------------
437           endif
438c---------------------------
439          enddo  !nlon
440         enddo  !nstep
441     
442      END IF  ! diurnal cycle
443
444      return
445      end
446
447     
448      subroutine interpnir(escout,p,nlev,escin,pin,nl)
449C
450C subroutine to perform linear interpolation in pressure from 1D profile
451C escin(nl) sampled on pressure grid pin(nl) to profile
452C escout(nlev) on pressure grid p(nlev).
453C
454      real escout(nlev),p(nlev)
455      real escin(nl),pin(nl),wm,wp
456      integer nl,nlev,n1,n,nm,np
457      do n1=1,nlev
458         if(p(n1) .gt. 1500. .or. p(n1) .lt. 1.0e-13) then
459c            escout(n1) = 0.0
460            escout(n1) = 1.e-15
461         else
462            do n = 1,nl-1
463               if (p(n1).le.pin(n).and.p(n1).ge.pin(n+1)) then
464                  nm=n
465                  np=n+1
466                  wm=abs(pin(np)-p(n1))/(pin(nm)-pin(np))
467                  wp=1.0 - wm
468               endif
469            enddo
470            escout(n1) = escin(nm)*wm + escin(np)*wp
471         endif
472      enddo
473      return
474      end
Note: See TracBrowser for help on using the repository browser.