source: flexpart.git/src/get_settling.f90 @ 3481cc1

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file since 3481cc1 was 3481cc1, checked in by Ignacio Pisso <ip@…>, 4 years ago

move license from headers to a different file

  • Property mode set to 100644
File size: 4.4 KB
Line 
1subroutine get_settling(itime,xt,yt,zt,nsp,settling)
2  !                          i   i  i  i   i     o
3  !*****************************************************************************
4  !                                                                            *
5  !  This subroutine calculates particle settling velocity.                    *
6  !                                                                            *
7  !    Author: A. Stohl                                                        *
8  !                                                                            *
9  !    May 2010                                                                *
10  !                                                                            *
11  !  Improvement over traditional settling calculation in FLEXPART:            *
12  !  generalize to higher Reynolds numbers and also take into account the      *
13  !  temperature dependence of dynamic viscosity.                              *
14  !                                                                            *
15  !  Based on:                                                                 *
16  !  Naeslund E., and Thaning, L. (1991): On the settling velocity in a        *
17  !  nonstationary atmosphere, Aerosol Science and Technology 14, 247-256.     *
18  !                                                                            *
19  !*****************************************************************************
20  !                                                                            *
21  ! Variables:                                                                 *
22  ! itime [s]          current temporal position                               *
23  ! xt,yt,zt           coordinates position for which wind data shall be cal-  *
24  !                    culated                                                 *
25  !                                                                            *
26  ! Constants:                                                                 *
27  !                                                                            *
28  !*****************************************************************************
29
30  use par_mod
31  use com_mod
32
33  implicit none
34
35  integer :: itime,indz
36  real :: xt,yt,zt
37
38  ! Auxiliary variables needed for interpolation
39  real :: dz1,dz2,dz
40  real :: rho1(2),tt1(2),temperature,airdens,vis_dyn,vis_kin,viscosity
41  real :: settling,settling_old,reynolds,c_d
42  integer :: i,n,nix,njy,indzh,nsp
43
44
45  !*****************************************************************************
46  ! 1. Interpolate temperature and density: nearest neighbor interpolation sufficient
47  !*****************************************************************************
48
49  nix=int(xt)
50  njy=int(yt)
51
52  ! Determine the level below the current position for u,v
53  !*******************************************************
54
55  do i=2,nz
56    if (height(i).gt.zt) then
57      indz=i-1
58      goto 6
59    endif
60  end do
616   continue
62
63
64  ! Vertical distance to the level below and above current position
65  !****************************************************************
66
67  dz=1./(height(indz+1)-height(indz))
68  dz1=(zt-height(indz))*dz
69  dz2=(height(indz+1)-zt)*dz
70
71
72  ! Bilinear horizontal interpolation
73  !**********************************
74
75  ! Loop over 2 levels
76  !*******************
77
78  do n=1,2
79    indzh=indz+n-1
80    rho1(n)=rho(nix,njy,indzh,1)
81    tt1(n)=tt(nix,njy,indzh,1)
82  end do
83
84
85  ! Linear vertical interpolation
86  !******************************
87
88  temperature=dz2*tt1(1)+dz1*tt1(2)
89  airdens=dz2*rho1(1)+dz1*rho1(2)
90
91
92  vis_dyn=viscosity(temperature)
93  vis_kin=vis_dyn/airdens
94
95  reynolds=dquer(nsp)/1.e6*abs(vsetaver(nsp))/vis_kin
96
97
98
99  ! Iteration to determine both Reynolds number and settling velocity
100  !******************************************************************
101
102  settling_old=vsetaver(nsp)    ! initialize iteration with Stokes' law, constant viscosity estimate
103
104  do i=1,20    ! do a few iterations
105
106    if (reynolds.lt.1.917) then
107      c_d=24./reynolds
108    else if (reynolds.lt.500.) then
109      c_d=18.5/(reynolds**0.6)
110    else
111      c_d=0.44
112    endif
113
114    settling=-1.* &
115         sqrt(4*ga*dquer(nsp)/1.e6*density(nsp)*cunningham(nsp)/ &
116         (3.*c_d*airdens))
117
118    if (abs((settling-settling_old)/settling).lt.0.01) goto 11  ! stop iteration
119
120    reynolds=dquer(nsp)/1.e6*abs(settling)/vis_kin
121    settling_old=settling
122  end do
123
12411   continue
125
126end subroutine get_settling
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG