[1648] | 1 | subroutine disr_haze(dz,press,wno,taeros,ssa,cbar) |
---|
[1663] | 2 | |
---|
[1648] | 3 | use datafile_mod, only: datadir |
---|
[1663] | 4 | |
---|
[1648] | 5 | IMPLICIT NONE |
---|
| 6 | |
---|
[1663] | 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 | ! |
---|
[3090] | 19 | ! Modified : |
---|
| 20 | ! B. de Batz de Trenquelléon (2022) |
---|
[1663] | 21 | ! ========================================================================== |
---|
[1648] | 22 | |
---|
[1663] | 23 | real*8,intent(in) :: dz, press, wno |
---|
| 24 | real*8,intent(inout):: taeros, ssa, cbar |
---|
| 25 | |
---|
[1648] | 26 | !--------------------------- |
---|
[1663] | 27 | ! NB !! |
---|
[1648] | 28 | ! taeros is the integrated extinction over the layer |
---|
| 29 | ! (extinction * thickness of layer) |
---|
| 30 | !--------------------------- |
---|
| 31 | |
---|
[1663] | 32 | integer :: i, j, iw, ip, ierr |
---|
| 33 | real*8 :: wln, factw, factp |
---|
[1681] | 34 | real*8 :: tmp_p, fact_t |
---|
[1663] | 35 | integer,parameter :: nbwl_PL=328, nblev_PL=162 |
---|
[1792] | 36 | real*8,save :: ext_PL(nblev_PL,nbwl_PL), ssa_PL(nblev_PL,nbwl_PL), asf_PL(nblev_PL,nbwl_PL) |
---|
[1663] | 37 | real*8,save :: wl_PL(nbwl_PL), press_PL(nblev_PL) |
---|
[1648] | 38 | logical,save :: firstcall=.true. |
---|
| 39 | character(len=15) :: dummy |
---|
| 40 | |
---|
[1792] | 41 | !$OMP THREADPRIVATE(ext_PL,ssa_PL,asf_PL,wl_PL,press_PL,firstcall) |
---|
| 42 | |
---|
[1648] | 43 | if (firstcall) then |
---|
[1663] | 44 | print*,"We use DISR haze mean profile from P.Lavvas" |
---|
[1648] | 45 | |
---|
| 46 | ! read PL table |
---|
| 47 | ! wl_PL in nm |
---|
| 48 | ! press_PL in Pa |
---|
[3083] | 49 | open(11,file=TRIM(datadir)//'/optical_tables/hazetable_PL_original.dat',status="old",iostat=ierr) |
---|
[1648] | 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) |
---|
[1663] | 61 | ! convert press_PL into millibar for comparison to press in the generic |
---|
[1648] | 62 | press_PL(:)=press_PL(:)*1E-2 |
---|
[1663] | 63 | |
---|
[1648] | 64 | firstcall=.false. |
---|
| 65 | endif |
---|
| 66 | |
---|
| 67 | ! convert wno (in cm-1) into wln (nm) |
---|
| 68 | wln=1E7/wno |
---|
| 69 | |
---|
| 70 | ! interpolate the needed values from the table |
---|
| 71 | |
---|
| 72 | iw=1 |
---|
| 73 | do i=2,nbwl_PL |
---|
| 74 | if(wln.gt.wl_PL(i)) then |
---|
| 75 | iw=i |
---|
| 76 | endif |
---|
| 77 | enddo |
---|
| 78 | |
---|
| 79 | ip=1 |
---|
| 80 | do j=2,nblev_PL |
---|
| 81 | if(press.lt.press_PL(j)) then |
---|
| 82 | ip=j |
---|
| 83 | endif |
---|
| 84 | enddo |
---|
| 85 | |
---|
[1663] | 86 | !----------------- Interpolate values from the hazetable -------------------- |
---|
[1681] | 87 | if (iw.ne. nbwl_PL) then |
---|
[1663] | 88 | factw = (wln-wl_PL(iw)) / (wl_PL(iw+1)-wl_PL(iw)) |
---|
[1648] | 89 | endif |
---|
[1681] | 90 | |
---|
| 91 | if (ip .ne. nblev_PL) then |
---|
[1663] | 92 | factp = (press-press_PL(ip)) / (press_PL(ip+1)-press_PL(ip)) |
---|
[1648] | 93 | endif |
---|
| 94 | |
---|
[1663] | 95 | ! Lin-Log interpolation : linear on wln, logarithmic on press |
---|
| 96 | |
---|
[1681] | 97 | if((ip.ne.nblev_PL) .and. (iw.ne.nbwl_PL)) then |
---|
| 98 | |
---|
[1663] | 99 | taeros = ( 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 | |
---|
| 102 | ssa = ( 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 | |
---|
| 105 | cbar = ( 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 | |
---|
[1681] | 108 | else if ((ip.ne.nblev_PL) .and. (iw.eq.nbwl_PL)) then |
---|
[1672] | 109 | |
---|
[2040] | 110 | taeros = ext_PL(ip,iw)**(1.-factp) * ext_PL(ip+1,iw)**factp |
---|
[1681] | 111 | ssa = ssa_PL(ip,iw)**(1.-factp) * ssa_PL(ip+1,iw)**factp |
---|
| 112 | cbar = asf_PL(ip,iw)**(1.-factp) * asf_PL(ip+1,iw)**factp |
---|
[1672] | 113 | |
---|
[1681] | 114 | |
---|
[1663] | 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 |
---|
[1681] | 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) |
---|
[1663] | 120 | |
---|
[1672] | 121 | else if(ip.eq.nblev_PL) then |
---|
[1663] | 122 | |
---|
| 123 | tmp_p = press |
---|
| 124 | |
---|
| 125 | if ( tmp_p .lt. 1.E-15 ) then |
---|
| 126 | tmp_p = 1.E-15 |
---|
| 127 | endif |
---|
| 128 | |
---|
[1681] | 129 | if(iw.ne.nbwl_PL) then |
---|
[1663] | 130 | |
---|
[1681] | 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 ) ) |
---|
[1792] | 133 | |
---|
[2040] | 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 |
---|
[1681] | 137 | |
---|
| 138 | else if (iw.eq.nbwl_PL) then |
---|
| 139 | |
---|
[1792] | 140 | fact_t = log10( ext_PL(ip,iw) / ext_PL(ip-5,iw) ) |
---|
| 141 | |
---|
[2040] | 142 | taeros = ext_PL(ip,iw) |
---|
| 143 | ssa = ssa_PL(ip,iw) |
---|
| 144 | cbar = asf_PL(ip,iw) |
---|
[1681] | 145 | |
---|
| 146 | endif |
---|
| 147 | |
---|
[1663] | 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 | |
---|
[1648] | 152 | endif |
---|
| 153 | |
---|
| 154 | taeros=taeros*dz*1.E2 ! ext in cm-1 * thickness in m * 1E2 |
---|
| 155 | |
---|
| 156 | end subroutine disr_haze |
---|