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

Last change on this file since 1530 was 1530, checked in by emillour, 9 years ago

Venus and Titan GCMs:
Updates in the physics to keep up with updates in LMDZ5 (up to
LMDZ5 trunk, rev 2350) concerning dynamics/physics separation:

  • Adapted makelmdz and makelmdz_fcm script to stop if trying to compile 1d model or newstart or start2archive in parallel.
  • got rid of references to "dimensions.h" in physics. Within physics packages, use nbp_lon (=iim), nbp_lat (=jjmp1) and nbp_lev (=llm) from module mod_grid_phy_lmdz (in phy_common) instead. Only partially done for Titan, because of many hard-coded commons; a necessary first step will be to clean these up (using modules).

EM

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 "YOMCST.h"
57#include "clesphys.h"
58c#include "comdiurn.h"
59#include "nirdata.h"
60c#include "tracer.h"
61#include "mmol.h"
62c-----------------------------------------------------------------------
63c    Input/Output
64c    ------------
65      integer,intent(in) :: nlon ! number of (horizontal) grid points
66      integer,intent(in) :: nlev ! number of atmospheric layers
67
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) ! mass mixing ratio 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      real :: co2vmr_gcm(nlon,nlev), o3pvmr_gcm(nlon,nlev)
76 
77      real,intent(out) :: pdtnirco2(nlon,nlev) ! heating rate (K/sec)
78
79c
80c    Local variables :
81c    -----------------
82      INTEGER l,ig, n, nstep,i
83      REAL co2heat0, zmu(nlon)
84
85c     special diurnal=F
86      real mu0_int(nlon),fract_int(nlon),zday_int
87      real ztim1,ztim2,ztim3,step
88
89c
90c   local saved variables
91c   ---------------------
92      logical,save :: firstcall=.true.
93      integer,save :: ico2=0 ! index of "co2" tracer
94      integer,save :: io=0 ! index of "o" tracer
95
96cccc     parameters for CO2 heating fit
97c
98c     n_a  =  heating rate for Venusian day at p0, r0, mu =0 [K day-1]
99c     Here p0 = p_cloud top [Pa]
100c     n_p0 = is a pressure below which non LTE effects are significant [Pa]
101c     n_a Solar heating [K/Eday] at the cloud top, taken from Crisps table     
102 
103      real n_a, n_p0, n_b, p_ctop
104
105   
106cc "Nominal" values
107       parameter (n_a = 18.13/86400.0)     !c     K/Eday  ---> K/sec   
108       parameter (p_ctop=13.2e2)
109c    -- NLTE Param v3  --
110       parameter (n_p0=0.008) 
111       parameter (n_b=1.362)
112
113cc   -- Varoxy5
114C       parameter (n_a = 20/86400.0)
115C       parameter (p_ctop=870)   ! [Pa]
116C       parameter (n_b=1.98)
117C       parameter (n_p0=0.045)
118
119c      parameter (n_p0=0.1) !!!!cccc test varoxy5mod
120c      parameter (n_b=0.9)
121
122
123c    -- NLTE Param v2  --
124C       parameter (n_p0=0.01) 
125c       parameter (n_b = 1.3)
126   
127
128
129c     Variables added to implement NLTE correction factor (feb 2011)
130      real    pyy(nlev)
131      real    cor1(nlev),oldoco2(nlev),alfa2(nlev)
132      real    p2011,cociente1,merge
133      real    cor0,oco2gcm
134!!!!
135c      real :: pic27(nlon,nlev), pic27b(nlon,nlev)
136c      real :: pic43(nlon,nlev), picnir(nlon,nlev)
137
138c     co2heat is the heating by CO2 at p_ctop=13.2e2 for a zero zenithal angle.
139
140      co2heat0=n_a*(0.72/dist_sol)**2     
141
142CCCCCC   TEST: reduce by X% nir Heating
143
144c      co2heat0  = co2heat0 * 0.8
145
146
147c----------------------------------------------------------------------
148     
149c     Initialisation
150c     --------------
151      if (firstcall) then
152        if (nircorr.eq.1) then
153c          ! we will need co2 and o tracers
154          ico2= i_co2
155          if (ico2==0) then
156            write(*,*) "nirco2abs error: I need a CO2 tracer"
157            write(*,*) "     when running with nircorr==1"
158           stop
159          endif
160          io=i_o
161          if (io==0) then
162            write(*,*) "nirco2abs error: I need an O tracer"
163            write(*,*) "     when running with nircorr==1"
164            stop
165          endif
166        endif
167        firstcall=.false.
168      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
193     
194c           Calculations for the O/CO2 correction
195               if(nircorr.eq.1) then
196                  cor0=1./(1.+n_p0/nplay(ig,l))**n_b
197                  if(pq(ig,l,ico2) .gt. 1.e-6) then
198                     oco2gcm=pq(ig,l,io)/pq(ig,l,ico2)
199
200                  else
201                     oco2gcm=1.e6
202                  endif
203                  cociente1=oco2gcm/oldoco2(l)
204                 
205c                  WRITE(*,*) "nirco2abs line 211", l, cociente1
206
207                  merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
208     $                 (1.-alfa2(l))
209                  merge=10**merge
210                  p2011=sqrt(merge)*cor0
211
212               else if (nircorr.eq.0) then
213                  p2011=1.
214                  cor1(l)=1.
215               endif
216
217              if(fract(ig).gt.0.) pdtnirco2(ig,l)=
218     &             co2heat0*sqrt((p_ctop*zmu(ig))/nplay(ig,l))
219     &             /(1.+n_p0/nplay(ig,l))**n_b
220c           Corrections from tabulation
221     $              * cor1(l) * p2011
222             
223          enddo
224         enddo
225         
226c     Averaging over diurnal cycle (if diurnal=F)
227c     -------------------------------------------
228c     NIR CO2 abs is slightly non linear. To remove the diurnal
229c     cycle, it is better to average the heating rate over 1 day rather
230c     than using the mean mu0 computed by mucorr in physiq.F (FF, 1998)
231
232      ELSE      ! if (.not.diurnal) then
233         nstep = 20    ! number of integration step /sol
234         do n=1,nstep
235
236            zday_int = (n-1)/float(nstep)
237
238            CALL zenang(0.,zday_int,RDAY/nstep,rlatd,rlond,
239     s             mu0_int,fract_int)
240
241            do ig=1,nlon
242               zmu(ig)=sqrt(1224.*mu0_int(ig)*mu0_int(ig)+1.)/35.
243
244               if(nircorr.eq.1) then
245                  do l=1,nlev
246                     pyy(l)=nplay(ig,l)
247                  enddo
248                 call interpnir(cor1,pyy,nlev,corgcm,pres1d,npres)
249                 call interpnir(oldoco2,pyy,nlev,oco21d,pres1d,npres)
250                 call interpnir(alfa2,pyy,nlev,alfa,pres1d,npres)
251               endif
252c
253
254               do l=1,nlev
255c           Calculations for the O/CO2 correction
256               if(nircorr.eq.1) then
257                  cor0=1./(1.+n_p0/nplay(ig,l))**n_b
258                  oco2gcm=pq(ig,l,io)/pq(ig,l,ico2)
259                  cociente1=oco2gcm/oldoco2(l)
260                  merge=alog10(cociente1)*alfa2(l)+alog10(cor0)*
261     $                 (1.-alfa2(l))
262                  merge=10**merge
263                  p2011=sqrt(merge)*cor0
264
265               else if (nircorr.eq.0) then
266                  p2011=1.
267                  cor1(l)=1.
268               endif
269
270               if(fract_int(ig).gt.0.) pdtnirco2(ig,l)=
271     &              pdtnirco2(ig,l) + (1/float(nstep))*
272     &              co2heat0*sqrt((p_ctop*zmu(ig))/nplay(ig,l))
273     &              /(1.+n_p0/nplay(ig,l))**n_b
274!     Corrections from tabulation
275     $              * cor1(l) * p2011
276
277               enddo
278            enddo
279         end do
280     
281
282      END IF 
283
284      return
285      end
286
287     
288      subroutine interpnir(escout,p,nlev,escin,pin,nl)
289C
290C subroutine to perform linear interpolation in pressure from 1D profile
291C escin(nl) sampled on pressure grid pin(nl) to profile
292C escout(nlev) on pressure grid p(nlev).
293C
294      real escout(nlev),p(nlev)
295      real escin(nl),pin(nl),wm,wp
296      integer nl,nlev,n1,n,nm,np
297      do n1=1,nlev
298         if(p(n1) .gt. 1500. .or. p(n1) .lt. 1.0e-13) then
299c            escout(n1) = 0.0
300            escout(n1) = 1.e-15
301         else
302            do n = 1,nl-1
303               if (p(n1).le.pin(n).and.p(n1).ge.pin(n+1)) then
304                  nm=n
305                  np=n+1
306                  wm=abs(pin(np)-p(n1))/(pin(nm)-pin(np))
307                  wp=1.0 - wm
308               endif
309            enddo
310            escout(n1) = escin(nm)*wm + escin(np)*wp
311         endif
312      enddo
313      return
314      end
Note: See TracBrowser for help on using the repository browser.