source: trunk/LMDZ.GENERIC/libf/phystd/calc_rayleigh.F90 @ 2613

Last change on this file since 2613 was 2529, checked in by emillour, 4 years ago

Generic GCM:
Cosmetic changes in calc_rayleigh.
EM

File size: 5.9 KB
Line 
1      subroutine calc_rayleigh
2
3!==================================================================
4!     
5!     Purpose
6!     -------
7!     Average the Rayleigh scattering in each band, weighting the
8!     average by the blackbody function at temperature tstellar.
9!     Works for an arbitrary mix of gases (currently CO2, N2 and
10!     H2 are possible).
11!     
12!     Authors
13!     -------
14!     Robin Wordsworth (2010)
15!     Jeremy Leconte (2012): Added option for variable gas. Improved water rayleigh (Bucholtz 1995).
16!
17!     Called by
18!     ---------
19!     setspv.F
20!     
21!     Calls
22!     -----
23!     none
24!     
25!==================================================================
26
27      use radinc_h, only: L_NSPECTV
28      use radcommon_h, only: WAVEV, BWNV, DWNV, tstellar, tauray, taurayvar, scalep
29      use gases_h, only: ngasmx, vgas, gnom, gfrac, igas_CO2, igas_H2, &
30                         igas_H2O, igas_He, igas_N2
31      use comcstfi_mod, only: g, mugaz
32
33      implicit none
34
35      real*8 wl
36      integer N,Nfine,ifine,igas
37      parameter(Nfine=500.0)
38      real*8 :: P0 = 9.423D+6   ! Rayleigh scattering reference pressure in pascals.   
39
40      logical typeknown
41      real*8 tauvar,tauvarvar,tausum,tausumvar,tauwei,tauweivar,bwidth,bstart
42      double precision df
43
44      real*8 tauconsti(ngasmx)
45      real*8 tauvari(ngasmx)
46
47      integer icantbewrong
48
49      ! tau0/p0=tau/p (Hansen 1974)
50      ! Then calculate tau0 = (8*pi^3*p_1atm)/(3*N0^2) * 4*delta^2/(g*mugaz*lambda^4)
51      ! where delta=n-1 and N0 is an amagat
52
53      typeknown=.false.
54      do igas=1,ngasmx
55         if(igas.eq.vgas)then
56            print*,'variable gas is ',trim(gnom(igas)),' in Rayleigh scattering '
57         endif
58         if((igas/=vgas).and.(gfrac(igas).lt.5.e-2))then
59            print*,'Ignoring ',trim(gnom(igas)),' in Rayleigh scattering '// &
60            'as its mixing ratio is less than 0.05.'
61            ! ignore variable gas in Rayleigh calculation
62            ! ignore gases of mixing ratio < 0.05 in Rayleigh calculation
63            tauconsti(igas) = 0.0
64         else
65            if(igas.eq.igas_CO2) then
66               tauconsti(igas) = (8.7/g)*1.527*scalep/P0
67            elseif(igas.eq.igas_N2)then
68               tauconsti(igas) = (9.81/g)*8.569E-3*scalep/(P0/93.0)
69            elseif(igas.eq.igas_H2O)then
70!               tauconsti(igas) = (10.0/g)*9.22E-3*scalep/101325.0
71               tauconsti(igas) = 1.98017E-10/(g*mugaz*100.)
72            elseif(igas.eq.igas_H2)then
73               tauconsti(igas) = (10.0/g)*0.0241*scalep/101325.0
74               !tauconsti(igas) = (10.0/g)*0.0487*scalep/(101325.0)
75               ! uses n=1.000132 from Optics, Fourth Edition.
76               ! was out by a factor 2!
77            elseif(igas.eq.igas_He)then
78               tauconsti(igas) = (10.0/g)*0.00086*scalep/101325.0
79            else
80               print*,'Error in calc_rayleigh: Gas species not recognised!'
81               print*,"igas=",igas," gnom(igas)=",trim(gnom(igas))
82               call abort_physic("calc_rayleigh","Invalid gas",1)
83            endif
84
85            if((gfrac(igas).eq.1.0).and.(vgas.eq.0))then
86               print*,'Rayleigh scattering is for a pure ',trim(gnom(igas)),' atmosphere.'
87               typeknown=.true.
88            endif
89
90         endif
91      enddo
92
93      if(.not.typeknown)then
94         print*,'Rayleigh scattering is for a mixed gas atmosphere.'
95         typeknown=.true.
96      endif
97
98 
99      do N=1,L_NSPECTV
100         
101         tausum = 0.0
102         tauwei = 0.0
103         tausumvar = 0.0
104         tauweivar = 0.0
105         bstart = 10000.0/BWNV(N+1)
106         bwidth = (10000.0/BWNV(N)) - (10000.0/BWNV(N+1))
107         do ifine=1,Nfine
108            wl=bstart+dble(ifine)*bwidth/Nfine
109
110            tauvar=0.0
111            tauvarvar=0.0
112            do igas=1,ngasmx
113               if((igas/=vgas).and.(gfrac(igas).lt.5.e-2))then
114                  ! ignore variable gas in Rayleigh calculation
115                  ! ignore gases of mixing ratio < 0.05 in Rayleigh calculation
116                  tauvari(igas)   = 0.0
117               else
118                  if(igas.eq.igas_CO2)then
119                     tauvari(igas) = (1.0+0.013/wl**2)/wl**4
120                  elseif(igas.eq.igas_N2)then
121                     tauvari(igas) = (1.0+0.0113/wl**2+0.00013/wl**4)/wl**4
122                  elseif(igas.eq.igas_H2O)then
123!                     tauvari(igas) = 1.0/wl**4 ! to be improved...
124                     tauvari(igas) = (5.7918E6/(2.38E2-1/wl**2)+1.679E5/(57.36E0-1/wl**2))**2/wl**4
125                  elseif(igas.eq.igas_H2)then
126                     tauvari(igas) = 1.0/wl**4
127                  elseif(igas.eq.igas_He)then
128                     tauvari(igas) = 1.0/wl**4
129                  else
130                     print*,'Error in calc_rayleigh: Gas species not recognised!'
131                     call abort_physic("calc_rayleigh","Gas species not recognised",1)
132                  endif
133               endif
134
135               if(igas.eq.vgas) then
136                  tauvarvar=tauvarvar+tauconsti(igas)*tauvari(igas)
137                  tauvar=tauvar+0.0*0.0*gfrac(igas)
138               else
139                  tauvar=tauvar+tauconsti(igas)*tauvari(igas)*gfrac(igas)
140               endif
141
142            enddo
143
144            call blackl(dble(wl*1e-6),dble(tstellar),df)
145            df=df*bwidth/Nfine
146            tauwei=tauwei+df
147            tausum=tausum+tauvar*df
148            tauweivar=tauweivar+df
149            tausumvar=tausumvar+tauvarvar*df
150         
151         enddo
152         TAURAY(N)=tausum/tauwei
153         TAURAYVAR(N)=tausumvar/tauweivar
154         ! we multiply by scalep here (100) because plev, which is used in optcv,
155         ! is in units of mBar, so we need to convert.
156
157      end do
158
159      IF (L_NSPECTV > 6) THEN
160        icantbewrong = L_NSPECTV-6
161        print*,'At 1 atm and lambda = ',WAVEV(icantbewrong),' um'
162        print*,'tau_R = ',TAURAY(icantbewrong)*1013.25
163        print*,'sig_R = ',TAURAY(icantbewrong)*g*mugaz*1.67e-27*100, &
164               'cm^2 molecule^-1'
165      ENDIF
166
167    end subroutine calc_rayleigh
Note: See TracBrowser for help on using the repository browser.