Line data Source code
1 : !===============================================================================
2 : ! Dust for Bulk Aerosol Model
3 : !===============================================================================
4 : module dust_model
5 : use shr_kind_mod, only: r8 => shr_kind_r8, cl => shr_kind_cl
6 : use spmd_utils, only: masterproc
7 : use cam_abortutils, only: endrun
8 : use cam_logfile, only: iulog
9 : use shr_dust_emis_mod,only: is_dust_emis_zender, is_zender_soil_erod_from_atm
10 :
11 : implicit none
12 : private
13 :
14 : public :: dust_active
15 : public :: dust_names
16 : public :: dust_nbin
17 : public :: dust_indices
18 : public :: dust_emis
19 : public :: dust_readnl
20 : public :: dust_init
21 :
22 : public :: dust_depvel
23 :
24 : logical :: dust_active = .false.
25 :
26 : integer, parameter :: dust_nbin = 4
27 : integer, parameter :: dust_nnum = 0
28 :
29 : character(len=6), parameter :: dust_names(dust_nbin) &
30 : = (/'DST01 ', 'DST02 ', 'DST03 ', 'DST04 '/)
31 :
32 : real(r8), parameter :: dust_dmt_grd(dust_nbin+1) &
33 : = (/ 0.1e-6_r8, 1.0e-6_r8, 2.5e-6_r8, 5.0e-6_r8, 10.0e-6_r8 /)
34 :
35 : integer :: dust_indices(dust_nbin)
36 : real(r8) :: dust_dmt_vwr(dust_nbin)
37 : real(r8) :: dust_stk_crc(dust_nbin)
38 :
39 : real(r8) :: dust_emis_fact = -1.e36_r8 ! tuning parameter for dust emissions
40 : character(len=cl) :: soil_erod_file = 'none' ! full pathname for soil erodibility dataset
41 :
42 : contains
43 :
44 : !=============================================================================
45 : ! reads dust namelist options
46 : !=============================================================================
47 0 : subroutine dust_readnl(nlfile)
48 :
49 : use namelist_utils, only: find_group_name
50 : use spmd_utils, only: mpicom, masterprocid, mpi_character, mpi_real8, mpi_success
51 : use shr_dust_emis_mod, only: shr_dust_emis_readnl
52 :
53 : character(len=*), intent(in) :: nlfile ! filepath for file containing namelist input
54 :
55 : ! Local variables
56 : integer :: unitn, ierr
57 : character(len=*), parameter :: subname = 'dust_readnl'
58 :
59 : namelist /dust_nl/ dust_emis_fact, soil_erod_file
60 :
61 : !-----------------------------------------------------------------------------
62 :
63 : ! Read namelist
64 0 : if (masterproc) then
65 0 : open( newunit=unitn, file=trim(nlfile), status='old' )
66 0 : call find_group_name(unitn, 'dust_nl', status=ierr)
67 0 : if (ierr == 0) then
68 0 : read(unitn, dust_nl, iostat=ierr)
69 0 : if (ierr /= 0) then
70 0 : call endrun(subname // ':: ERROR reading namelist')
71 : end if
72 : end if
73 0 : close(unitn)
74 : end if
75 :
76 : ! Broadcast namelist variables
77 0 : call mpi_bcast(soil_erod_file, len(soil_erod_file), mpi_character, masterprocid, mpicom, ierr)
78 0 : if (ierr/=mpi_success) then
79 0 : call endrun(subname//' MPI_BCAST ERROR: soil_erod_file')
80 : end if
81 0 : call mpi_bcast(dust_emis_fact, 1, mpi_real8, masterprocid, mpicom, ierr)
82 0 : if (ierr/=mpi_success) then
83 0 : call endrun(subname//' MPI_BCAST ERROR: dust_emis_fact')
84 : end if
85 :
86 0 : call shr_dust_emis_readnl(mpicom, 'drv_flds_in')
87 :
88 0 : if ((soil_erod_file /= 'none') .and. (.not.is_zender_soil_erod_from_atm())) then
89 0 : call endrun(subname//': should not specify soil_erod_file if Zender soil erosion is not in CAM')
90 : end if
91 :
92 0 : if (masterproc) then
93 0 : if (is_dust_emis_zender()) then
94 0 : write(iulog,*) subname,': Zender_2003 dust emission method is being used.'
95 : end if
96 0 : if (is_zender_soil_erod_from_atm()) then
97 0 : write(iulog,*) subname,': Zender soil erod file is handled in atm'
98 0 : write(iulog,*) subname,': soil_erod_file = ',trim(soil_erod_file)
99 0 : write(iulog,*) subname,': dust_emis_fact = ',dust_emis_fact
100 : end if
101 : end if
102 :
103 0 : end subroutine dust_readnl
104 :
105 : !=============================================================================
106 : !=============================================================================
107 1536 : subroutine dust_init()
108 : use soil_erod_mod, only: soil_erod_init
109 : use constituents, only: cnst_get_ind
110 : use dust_common, only: dust_set_params
111 :
112 : integer :: n
113 :
114 7680 : do n = 1, dust_nbin
115 7680 : call cnst_get_ind(dust_names(n), dust_indices(n),abort=.false.)
116 : end do
117 7680 : dust_active = any(dust_indices(:) > 0)
118 1536 : if (.not.dust_active) return
119 :
120 0 : if (is_zender_soil_erod_from_atm()) then
121 0 : call soil_erod_init( dust_emis_fact, soil_erod_file )
122 : endif
123 :
124 0 : call dust_set_params( dust_nbin, dust_dmt_grd, dust_dmt_vwr, dust_stk_crc )
125 :
126 : end subroutine dust_init
127 :
128 : !==============================================================================
129 : !==============================================================================
130 0 : subroutine dust_emis( ncol, lchnk, dust_flux_in, cflx, soil_erod )
131 : use soil_erod_mod, only : soil_erod_fact
132 : use soil_erod_mod, only : soil_erodibility
133 : use cam_history_support, only : fillvalue
134 :
135 : ! args
136 : integer, intent(in) :: ncol, lchnk
137 : real(r8), intent(in) :: dust_flux_in(:,:)
138 : real(r8), intent(inout) :: cflx(:,:)
139 : real(r8), intent(out) :: soil_erod(:)
140 :
141 : ! local vars
142 : integer :: i, m, idst
143 : real(r8) :: erodfctr(ncol)
144 : real(r8), parameter :: dust_emis_sclfctr(dust_nbin) &
145 : = (/ 0.011_r8/0.032456_r8, 0.087_r8/0.174216_r8, 0.277_r8/0.4085517_r8, 0.625_r8/0.384811_r8 /)
146 :
147 : ! set dust emissions
148 :
149 0 : if (is_zender_soil_erod_from_atm()) then
150 :
151 0 : col_loop1: do i =1,ncol
152 :
153 0 : soil_erod(i) = soil_erodibility( i, lchnk )
154 :
155 : ! adjust emissions
156 0 : do m = 1,dust_nbin
157 :
158 0 : idst = dust_indices(m)
159 0 : cflx(i,idst) = -dust_flux_in(i,m) &
160 0 : * dust_emis_sclfctr(m)*soil_erod(i)/dust_emis_fact*1.15_r8
161 :
162 : enddo
163 :
164 : end do col_loop1
165 :
166 : else
167 :
168 0 : col_loop2: do i =1,ncol
169 :
170 : ! adjust emissions
171 0 : do m = 1,dust_nbin
172 :
173 0 : idst = dust_indices(m)
174 0 : cflx(i,idst) = -dust_flux_in(i,m) * dust_emis_sclfctr(m) / dust_emis_fact
175 :
176 : enddo
177 :
178 : end do col_loop2
179 :
180 : end if
181 :
182 0 : end subroutine dust_emis
183 :
184 : !===============================================================================
185 : !===============================================================================
186 0 : subroutine dust_depvel( temp, pmid, ram1, fv, ncol, vlc_dry,vlc_trb,vlc_grv )
187 0 : use aerosol_depvel, only: aerosol_depvel_compute
188 : use mo_constants, only: dust_density
189 : use ppgrid, only: pver
190 :
191 : real(r8), intent(in) :: temp(:,:) ! temperature
192 : real(r8), intent(in) :: pmid(:,:) ! mid point pressure
193 : real(r8), intent(in) :: ram1(:) ! aerodynamical resistance (s/m)
194 : real(r8), intent(in) :: fv(:) ! friction velocity (m/s)
195 : integer, intent(in) :: ncol
196 :
197 : real(r8), intent(out) :: vlc_trb(:,:) !Turbulent deposn velocity (m/s)
198 : real(r8), intent(out) :: vlc_grv(:,:,:) !grav deposn velocity (m/s)
199 : real(r8), intent(out) :: vlc_dry(:,:,:) !dry deposn velocity (m/s)
200 :
201 0 : real(r8) :: diam(ncol,pver,dust_nbin)
202 : integer :: m
203 :
204 0 : do m=1,dust_nbin
205 0 : diam(:,:,m) = dust_dmt_vwr(m)
206 : enddo
207 : call aerosol_depvel_compute( ncol, pver, dust_nbin, temp, pmid, ram1, fv, diam, dust_stk_crc, dust_density, &
208 0 : vlc_dry,vlc_trb,vlc_grv)
209 0 : endsubroutine dust_depvel
210 :
211 : end module dust_model
|