source: trunk/MESOSCALE/LMDZ.MARS/libf_gcm/phymars/nirco2abs.F @ 1242

Last change on this file since 1242 was 57, checked in by aslmd, 14 years ago

mineur LMD_MM_MARS: ajout du GCM ancienne physique, systeme maintenant complet sur SVN (ne manque que la base de donnees d'etats initiaux)

File size: 4.2 KB
Line 
1      SUBROUTINE nirco2abs(ngrid,nlayer,pplay,dist_sol,
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
18
19c   08/2002 : correction for bug when running with diurnal=F
20c
21c   author:  Frederic Hourdin 1996
22c   ------
23c            Francois Forget 1999
24c
25c   input:
26c   -----
27c   ngrid                 number of gridpoint of horizontal grid
28c   nlayer                Number of layer
29c   dist_sol              sun-Mars distance (AU)
30c   mu0(ngridmx)         
31c   fract(ngridmx)        day fraction of the time interval
32c   declin                latitude of subslar point
33c
34c   output:
35c   -------
36c
37c   pdtnirco2(ngrid,nlayer)      Heating rate (K/s)
38c
39c
40c=======================================================================
41c
42c    0.  Declarations :
43c    ------------------
44c
45#include "dimensions.h"
46#include "dimphys.h"
47#include "comcstfi.h"
48#include "callkeys.h"
49#include "comdiurn.h"
50
51
52c-----------------------------------------------------------------------
53c    Input/Output
54c    ------------
55      INTEGER ngrid,nlayer
56
57      REAL pplay(ngrid,nlayer)
58      REAL dist_sol,mu0(ngridmx),fract(ngridmx),declin
59
60      REAL pdtnirco2(ngrid,nlayer)
61c
62c    Local variables :
63c    -----------------
64      INTEGER l,ig, n, nstep
65      REAL co2heat0, zmu(ngridmx)
66
67c     special diurnal=F
68      real mu0_int(ngridmx),fract_int(ngridmx),zday_int
69      real ztim1,ztim2,ztim3,step
70
71c
72c   local saved variables
73c   ---------------------
74
75c     p0noonlte is a pressure below which non LTE effects are significant.
76c     REAL p0nonlte
77c     DATA p0nonlte/7.5e-3/
78c     SAVE p0nonlte
79
80c     parameters for CO2 heating fit
81      real n_a, n_p0, n_b
82      parameter (n_a=1.1956475)
83      parameter (n_b=1.9628251)
84      parameter (n_p0=0.0015888279)
85
86c----------------------------------------------------------------------
87
88c     Initialisation
89c     --------------
90c     co2heat is the heating by CO2 at 700Pa for a zero zenithal angle.
91      co2heat0=n_a*(1.52/dist_sol)**2/daysec
92
93c     Simple calcul for a given sun incident angle (if diurnal=T)
94c     --------------------------------------------
95
96      IF (diurnal) THEN 
97         do ig=1,ngrid
98            zmu(ig)=sqrt(1224.*mu0(ig)*mu0(ig)+1.)/35.
99         enddo
100         do l=1,nlayer
101           do ig=1,ngrid
102             if(fract(ig).gt.0.) pdtnirco2(ig,l)=
103     &             co2heat0*sqrt((700.*zmu(ig))/pplay(ig,l))
104     &             /(1.+n_p0/pplay(ig,l))**n_b
105
106c           OLD SCHEME (forget et al. 1999)
107c    s           co2heat0*sqrt((700.*zmu(ig))/pplay(ig,l))
108c    s          / (1+p0nonlte/pplay(ig,l))
109           enddo
110         enddo
111
112c     Averaging over diurnal cycle (if diurnal=F)
113c     -------------------------------------------
114c     NIR CO2 abs is slightly non linear. To remove the diurnal
115c     cycle, it is better to average the heating rate over 1 day rather
116c     than using the mean mu0 computed by mucorr in physiq.F (FF, 1998)
117
118      ELSE      ! if (.not.diurnal) then
119
120         nstep = 20   ! number of integration step /sol
121         do n=1,nstep
122            zday_int = (n-1)/float(nstep)
123            ztim2=COS(declin)*COS(2.*pi*(zday_int-.5))
124            ztim3=-COS(declin)*SIN(2.*pi*(zday_int-.5))
125            CALL solang(ngrid,sinlon,coslon,sinlat,coslat,
126     s             ztim1,ztim2,ztim3,
127     s             mu0_int,fract_int)
128            do ig=1,ngrid
129               zmu(ig)=sqrt(1224.*mu0_int(ig)*mu0_int(ig)+1.)/35.
130            enddo
131            do l=1,nlayer
132               do ig=1,ngrid
133                  if(fract_int(ig).gt.0.) pdtnirco2(ig,l)=
134     &                 pdtnirco2(ig,l) + (1/float(nstep))*
135     &                 co2heat0*sqrt((700.*zmu(ig))/pplay(ig,l))
136     &                 /(1.+n_p0/pplay(ig,l))**n_b
137               enddo
138            enddo
139         end do
140      END IF
141
142      return
143      end
144
Note: See TracBrowser for help on using the repository browser.