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

Last change on this file since 3529 was 3090, checked in by slebonnois, 14 months ago

BdeBatz? : Cleans microphysics and makes few corrections for physics

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