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

Last change on this file since 1215 was 1047, checked in by emillour, 12 years ago

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

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