1 | subroutine disr_haze(dz,press,wno,taeros,ssa,cbar) |
---|
2 | |
---|
3 | use datafile_mod, only: datadir |
---|
4 | |
---|
5 | IMPLICIT 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 | |
---|
21 | real*8,intent(in) :: dz, press, wno |
---|
22 | real*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 | |
---|
30 | integer :: i, j, iw, ip, ierr |
---|
31 | real*8 :: wln, factw, factp |
---|
32 | real*8 :: tmp_p, fact_t |
---|
33 | integer,parameter :: nbwl_PL=328, nblev_PL=162 |
---|
34 | real*8,save :: ext_PL(nblev_PL,nbwl_PL), ssa_PL(nblev_PL,nbwl_PL), asf_PL(nblev_PL,nbwl_PL) |
---|
35 | real*8,save :: wl_PL(nbwl_PL), press_PL(nblev_PL) |
---|
36 | logical,save :: firstcall=.true. |
---|
37 | character(len=15) :: dummy |
---|
38 | |
---|
39 | !$OMP THREADPRIVATE(ext_PL,ssa_PL,asf_PL,wl_PL,press_PL,firstcall) |
---|
40 | |
---|
41 | if (firstcall) then |
---|
42 | print*,"We use DISR haze mean profile from P.Lavvas" |
---|
43 | |
---|
44 | ! read PL table |
---|
45 | ! wl_PL in nm |
---|
46 | ! press_PL in Pa |
---|
47 | open(11,file=TRIM(datadir)//'/hazetable_PL_original.dat',status="old",iostat=ierr) |
---|
48 | read(11,*) dummy,wl_PL |
---|
49 | do i=1,nblev_PL |
---|
50 | read(11,*) press_PL(i),ext_PL(i,:) ! in cm-1 |
---|
51 | enddo |
---|
52 | do i=1,nblev_PL |
---|
53 | read(11,*) press_PL(i),ssa_PL(i,:) |
---|
54 | enddo |
---|
55 | do i=1,nblev_PL |
---|
56 | read(11,*) press_PL(i),asf_PL(i,:) |
---|
57 | enddo |
---|
58 | close(11) |
---|
59 | ! convert press_PL into millibar for comparison to press in the generic |
---|
60 | press_PL(:)=press_PL(:)*1E-2 |
---|
61 | |
---|
62 | firstcall=.false. |
---|
63 | endif |
---|
64 | |
---|
65 | ! convert wno (in cm-1) into wln (nm) |
---|
66 | wln=1E7/wno |
---|
67 | |
---|
68 | ! interpolate the needed values from the table |
---|
69 | |
---|
70 | iw=1 |
---|
71 | do i=2,nbwl_PL |
---|
72 | if(wln.gt.wl_PL(i)) then |
---|
73 | iw=i |
---|
74 | endif |
---|
75 | enddo |
---|
76 | |
---|
77 | ip=1 |
---|
78 | do j=2,nblev_PL |
---|
79 | if(press.lt.press_PL(j)) then |
---|
80 | ip=j |
---|
81 | endif |
---|
82 | enddo |
---|
83 | |
---|
84 | !----------------- Interpolate values from the hazetable -------------------- |
---|
85 | if (iw.ne. nbwl_PL) then |
---|
86 | factw = (wln-wl_PL(iw)) / (wl_PL(iw+1)-wl_PL(iw)) |
---|
87 | endif |
---|
88 | |
---|
89 | if (ip .ne. nblev_PL) then |
---|
90 | factp = (press-press_PL(ip)) / (press_PL(ip+1)-press_PL(ip)) |
---|
91 | endif |
---|
92 | |
---|
93 | ! Lin-Log interpolation : linear on wln, logarithmic on press |
---|
94 | |
---|
95 | if((ip.ne.nblev_PL) .and. (iw.ne.nbwl_PL)) then |
---|
96 | |
---|
97 | taeros = ( ext_PL(ip,iw)*(1.-factw) + ext_PL(ip,iw+1) *factw ) ** (1.-factp) & |
---|
98 | *( ext_PL(ip+1,iw)*(1.-factw) + ext_PL(ip+1,iw+1)*factw ) ** factp |
---|
99 | |
---|
100 | ssa = ( ssa_PL(ip,iw)*(1.-factw) + ssa_PL(ip,iw+1) *factw ) ** (1.-factp) & |
---|
101 | *( ssa_PL(ip+1,iw)*(1.-factw) + ssa_PL(ip+1,iw+1)*factw ) ** factp |
---|
102 | |
---|
103 | cbar = ( asf_PL(ip,iw)*(1.-factw) + asf_PL(ip,iw+1) *factw ) ** (1.-factp) & |
---|
104 | *( asf_PL(ip+1,iw)*(1.-factw) + asf_PL(ip+1,iw+1)*factw ) ** factp |
---|
105 | |
---|
106 | else if ((ip.ne.nblev_PL) .and. (iw.eq.nbwl_PL)) then |
---|
107 | |
---|
108 | taeros = ext_PL(ip,iw)**(1.-factp) * ext_PL(ip+1,iw)**factp |
---|
109 | ssa = ssa_PL(ip,iw)**(1.-factp) * ssa_PL(ip+1,iw)**factp |
---|
110 | cbar = asf_PL(ip,iw)**(1.-factp) * asf_PL(ip+1,iw)**factp |
---|
111 | |
---|
112 | |
---|
113 | ! In case of vertical extension over the max of the table |
---|
114 | ! We take the scale height on the last 5 levels (more it's not quite log) |
---|
115 | ! Arbitray threshold pressure value, just to deal with the last level press=0 |
---|
116 | ! We do not touch to ssa and cbar and let them at the value of last level |
---|
117 | ! (extrap would lead to too dark aerosols) |
---|
118 | |
---|
119 | else if(ip.eq.nblev_PL) then |
---|
120 | |
---|
121 | tmp_p = press |
---|
122 | |
---|
123 | if ( tmp_p .lt. 1.E-15 ) then |
---|
124 | tmp_p = 1.E-15 |
---|
125 | endif |
---|
126 | |
---|
127 | if(iw.ne.nbwl_PL) then |
---|
128 | |
---|
129 | fact_t = log10( ( ext_PL(ip,iw)*(1.-factw) + ext_PL(ip,iw+1) *factw ) & |
---|
130 | / ( ext_PL(ip-5,iw)*(1.-factw) + ext_PL(ip-5,iw+1) *factw ) ) |
---|
131 | |
---|
132 | taeros = ext_PL(ip,iw)*(1.-factw) + ext_PL(ip,iw+1)*factw |
---|
133 | ssa = ssa_PL(ip,iw)*(1.-factw) + ssa_PL(ip,iw+1)*factw |
---|
134 | cbar = asf_PL(ip,iw)*(1.-factw) + asf_PL(ip,iw+1)*factw |
---|
135 | |
---|
136 | else if (iw.eq.nbwl_PL) then |
---|
137 | |
---|
138 | fact_t = log10( ext_PL(ip,iw) / ext_PL(ip-5,iw) ) |
---|
139 | |
---|
140 | taeros = ext_PL(ip,iw) |
---|
141 | ssa = ssa_PL(ip,iw) |
---|
142 | cbar = asf_PL(ip,iw) |
---|
143 | |
---|
144 | endif |
---|
145 | |
---|
146 | fact_t = fact_t / log10( press_PL(ip) / press_PL(ip-5) ) |
---|
147 | |
---|
148 | taeros = taeros * ( tmp_p / press_PL(ip) ) ** fact_t |
---|
149 | |
---|
150 | endif |
---|
151 | |
---|
152 | taeros=taeros*dz*1.E2 ! ext in cm-1 * thickness in m * 1E2 |
---|
153 | |
---|
154 | end subroutine disr_haze |
---|