source: trunk/LMDZ.MARS/libf/phymars/nirco2abs.F @ 501

Last change on this file since 501 was 498, checked in by emillour, 13 years ago

Mars GCM: Cleanup of the NLTE routines which have been packed together to limit the number of files.
Also enforced that file names are non-capitalized (needed by the create_make_gcm scripts to better evaluate dependencies when building the makefile).
FGG+EM

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