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

Last change on this file since 1266 was 1266, checked in by aslmd, 11 years ago

LMDZ.MARS
IMPORTANT CHANGE

  • Remove all reference/use of nlayermx and dimphys.h
  • Made use of automatic arrays whenever arrays are needed with dimension nlayer
  • Remove lots of obsolete reference to dimensions.h
  • Converted iono.h and param_v4.h into corresponding modules

(with embedded subroutine to allocate arrays)
(no arrays allocated if thermosphere not used)

  • Deleted param.h and put contents into module param_v4_h
  • Adapted testphys1d, newstart, etc...
  • Made DATA arrays in param_read to be initialized by subroutine

fill_data_thermos in module param_v4_h

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