1 | SUBROUTINE nirco2abs(ngrid,nlayer,pplay,dist_sol, |
---|
2 | $ mu0,fract,declin,pdtnirco2) |
---|
3 | |
---|
4 | IMPLICIT NONE |
---|
5 | c======================================================================= |
---|
6 | c subject: |
---|
7 | c -------- |
---|
8 | c Computing heating rate due to |
---|
9 | c absorption by CO2 in the near-infrared |
---|
10 | c This version includes NLTE effects |
---|
11 | c |
---|
12 | c (Scheme to be described in Forget et al., JGR, 2003) |
---|
13 | c (old Scheme described in Forget et al., JGR, 1999) |
---|
14 | c |
---|
15 | c This version updated with a new functional fit, |
---|
16 | c see NLTE correction-factor of Lopez-Valverde et al (1998) |
---|
17 | c Stephen Lewis 2000 |
---|
18 | c |
---|
19 | c 08/2002 : correction for bug when running with diurnal=F |
---|
20 | c |
---|
21 | c author: Frederic Hourdin 1996 |
---|
22 | c ------ |
---|
23 | c Francois Forget 1999 |
---|
24 | c |
---|
25 | c input: |
---|
26 | c ----- |
---|
27 | c ngrid number of gridpoint of horizontal grid |
---|
28 | c nlayer Number of layer |
---|
29 | c dist_sol sun-Mars distance (AU) |
---|
30 | c mu0(ngridmx) |
---|
31 | c fract(ngridmx) day fraction of the time interval |
---|
32 | c declin latitude of subslar point |
---|
33 | c |
---|
34 | c output: |
---|
35 | c ------- |
---|
36 | c |
---|
37 | c pdtnirco2(ngrid,nlayer) Heating rate (K/s) |
---|
38 | c |
---|
39 | c |
---|
40 | c======================================================================= |
---|
41 | c |
---|
42 | c 0. Declarations : |
---|
43 | c ------------------ |
---|
44 | c |
---|
45 | #include "dimensions.h" |
---|
46 | #include "dimphys.h" |
---|
47 | #include "comcstfi.h" |
---|
48 | #include "callkeys.h" |
---|
49 | #include "comdiurn.h" |
---|
50 | |
---|
51 | |
---|
52 | c----------------------------------------------------------------------- |
---|
53 | c Input/Output |
---|
54 | c ------------ |
---|
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) |
---|
61 | c |
---|
62 | c Local variables : |
---|
63 | c ----------------- |
---|
64 | INTEGER l,ig, n, nstep |
---|
65 | REAL co2heat0, zmu(ngridmx) |
---|
66 | |
---|
67 | c special diurnal=F |
---|
68 | real mu0_int(ngridmx),fract_int(ngridmx),zday_int |
---|
69 | real ztim1,ztim2,ztim3,step |
---|
70 | |
---|
71 | c |
---|
72 | c local saved variables |
---|
73 | c --------------------- |
---|
74 | |
---|
75 | c p0noonlte is a pressure below which non LTE effects are significant. |
---|
76 | c REAL p0nonlte |
---|
77 | c DATA p0nonlte/7.5e-3/ |
---|
78 | c SAVE p0nonlte |
---|
79 | |
---|
80 | c 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 | |
---|
86 | c---------------------------------------------------------------------- |
---|
87 | |
---|
88 | c Initialisation |
---|
89 | c -------------- |
---|
90 | c co2heat is the heating by CO2 at 700Pa for a zero zenithal angle. |
---|
91 | co2heat0=n_a*(1.52/dist_sol)**2/daysec |
---|
92 | |
---|
93 | c Simple calcul for a given sun incident angle (if diurnal=T) |
---|
94 | c -------------------------------------------- |
---|
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 | |
---|
106 | c OLD SCHEME (forget et al. 1999) |
---|
107 | c s co2heat0*sqrt((700.*zmu(ig))/pplay(ig,l)) |
---|
108 | c s / (1+p0nonlte/pplay(ig,l)) |
---|
109 | enddo |
---|
110 | enddo |
---|
111 | |
---|
112 | c Averaging over diurnal cycle (if diurnal=F) |
---|
113 | c ------------------------------------------- |
---|
114 | c NIR CO2 abs is slightly non linear. To remove the diurnal |
---|
115 | c cycle, it is better to average the heating rate over 1 day rather |
---|
116 | c 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 | |
---|