source: trunk/LMDZ.TITAN/libf/phytitan/disr_haze.F90 @ 1790

Last change on this file since 1790 was 1681, checked in by jvatant, 8 years ago

Update deftank + correct a bug in extrapolation in haze opacity table routine

File size: 4.0 KB
Line 
1subroutine disr_haze(dz,press,wno,taeros,ssa,cbar)
2
3use datafile_mod, only: datadir
4
5IMPLICIT NONE
6
7! ==========================================================================
8!
9!  Purpose :
10!    Interpolate values of extinction coefficient, single scattering albedo
11!    and asymetry factor from hazetable ( Lavvas et al. 2010, mean profile, no
12!    detached layer)
13!
14!    + JVO 2017 : Vertical extension out of table implemented
15!
16!  Author :
17!     Jan Vatant d'Ollone (2016)
18!
19! ==========================================================================
20
21real*8,intent(in)   :: dz, press, wno
22real*8,intent(inout):: taeros, ssa, cbar
23
24!---------------------------
25! NB !!
26! taeros is the integrated extinction over the layer
27! (extinction * thickness of layer)
28!---------------------------
29
30integer             :: i, j, iw, ip, ierr
31real*8              :: wln, factw, factp
32real*8              :: tmp_p, fact_t
33integer,parameter   :: nbwl_PL=328, nblev_PL=162
34real*8,save         :: ext_PL(nblev_PL,nbwl_PL), ssa_PL(nblev_PL,nbwl_PL)
35real*8,save         :: asf_PL(nblev_PL,nbwl_PL)
36real*8,save         :: wl_PL(nbwl_PL), press_PL(nblev_PL)
37logical,save        :: firstcall=.true.
38character(len=15)   :: dummy
39
40if (firstcall) then
41   print*,"We use DISR haze mean profile from P.Lavvas"
42
43! read PL table   
44! wl_PL in nm
45! press_PL in Pa
46   open(11,file=TRIM(datadir)//'/hazetable_PL_original.dat',status="old",iostat=ierr)
47   read(11,*) dummy,wl_PL
48   do i=1,nblev_PL
49     read(11,*) press_PL(i),ext_PL(i,:)  ! in cm-1
50   enddo
51   do i=1,nblev_PL
52     read(11,*) press_PL(i),ssa_PL(i,:)
53   enddo
54   do i=1,nblev_PL
55     read(11,*) press_PL(i),asf_PL(i,:)
56   enddo
57   close(11)
58   ! convert press_PL into millibar for comparison to press in the generic
59   press_PL(:)=press_PL(:)*1E-2
60   
61   firstcall=.false.
62endif
63
64! convert wno (in cm-1) into wln (nm)
65wln=1E7/wno
66
67! interpolate the needed values from the table
68
69iw=1
70do i=2,nbwl_PL
71  if(wln.gt.wl_PL(i)) then
72    iw=i
73  endif
74enddo
75
76ip=1
77do j=2,nblev_PL
78  if(press.lt.press_PL(j)) then
79    ip=j
80  endif
81enddo
82
83!----------------- Interpolate values from the hazetable  --------------------
84if (iw.ne. nbwl_PL) then
85  factw = (wln-wl_PL(iw)) / (wl_PL(iw+1)-wl_PL(iw))
86endif
87
88if (ip .ne. nblev_PL) then
89  factp = (press-press_PL(ip)) / (press_PL(ip+1)-press_PL(ip))
90endif
91
92! Lin-Log interpolation : linear on wln, logarithmic on press
93
94if((ip.ne.nblev_PL) .and. (iw.ne.nbwl_PL)) then
95
96taeros = ( ext_PL(ip,iw)*(1.-factw)   + ext_PL(ip,iw+1)  *factw ) ** (1.-factp) &
97        *( ext_PL(ip+1,iw)*(1.-factw) + ext_PL(ip+1,iw+1)*factw ) ** factp
98
99ssa    = ( ssa_PL(ip,iw)*(1.-factw)   + ssa_PL(ip,iw+1)  *factw ) ** (1.-factp) &
100        *( ssa_PL(ip+1,iw)*(1.-factw) + ssa_PL(ip+1,iw+1)*factw ) ** factp
101
102cbar   = ( asf_PL(ip,iw)*(1.-factw)   + asf_PL(ip,iw+1)  *factw ) ** (1.-factp) &
103        *( asf_PL(ip+1,iw)*(1.-factw) + asf_PL(ip+1,iw+1)*factw ) ** factp
104
105else if ((ip.ne.nblev_PL) .and. (iw.eq.nbwl_PL)) then
106
107taeros =  ext_PL(ip,iw)**(1.-factp)  * ext_PL(ip+1,iw)**factp
108       
109ssa    =  ssa_PL(ip,iw)**(1.-factp) * ssa_PL(ip+1,iw)**factp
110       
111cbar   =  asf_PL(ip,iw)**(1.-factp) * asf_PL(ip+1,iw)**factp
112
113
114! In case of vertical extension over the max of the table
115! We take the scale height on the last 5 levels (more it's not quite log)
116! Arbitray threshold pressure value, just to deal with the last level press=0
117! We do not touch to ssa and cbar and let them at the value of last level
118! (extrap would lead to too dark aerosols)
119
120else if(ip.eq.nblev_PL) then
121
122  tmp_p = press
123
124  if ( tmp_p .lt. 1.E-15 ) then
125    tmp_p = 1.E-15
126  endif
127
128  if(iw.ne.nbwl_PL) then 
129
130     fact_t = log10( ( ext_PL(ip,iw)*(1.-factw) + ext_PL(ip,iw+1)  *factw )   &
131           / ( ext_PL(ip-5,iw)*(1.-factw) + ext_PL(ip-5,iw+1)  *factw ) )
132
133  else if (iw.eq.nbwl_PL) then
134
135     fact_t = log10( ext_PL(ip,iw) / ext_PL(ip-5,iw) ) 
136
137  endif
138
139  fact_t = fact_t / log10( press_PL(ip) / press_PL(ip-5) )
140
141  taeros = taeros * ( tmp_p / press_PL(ip) ) ** fact_t
142
143endif
144
145taeros=taeros*dz*1.E2 ! ext in cm-1 * thickness in m * 1E2
146
147end subroutine disr_haze
Note: See TracBrowser for help on using the repository browser.