SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
dustflux_get.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 SUBROUTINE dustflux_get( &
6  pustar, &
7  prhoa, &
8  pwg, &
9  pz0, &
10  pwsat, &
11  pclay, &
12  psand, &
13  pwind10m, &
14  psfdst, &
15  ksize &
16  )
17 !
18 !PURPOSE:
19 !Take input from ISBA land surface model and
20 !calculate a dust flux which is consistent with the input.
21 
22 !THEORY:
23 !Based on Marticorena/Bergametti, 1995 and Zender et al 2003 (JGR)
24 
25 !CODE HISTORY
26 !Code is a modified version of dstmbl.F90 in the DEAD model
27 !Original version was downloaded from the DEAD homepage
28 !http://dust.ess.uci.edu/dead/ on January 10th 2005
29 
30 !AUTHOR (or rather "code modifyer")
31 !Alf Grini <alf.grini@cnrm.meteo.fr>
32 !
33 USE modd_dst_surf, ONLY : xflx_mss_fdg_fct
34 USE modd_dstmbl, ONLY : xrgh_mmn_smt, xcst_slt, xdmt_slt_opt
35 USE mode_dstmblutl !Dust mobilization subroutines
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 IMPLICIT NONE
41 !
42 !INPUT, set their dimensions to their passed lengths or to KSIZE ?
43 INTEGER, INTENT(IN) :: ksize ![nbr] length of passed arrays
44 REAL, INTENT(IN), DIMENSION(KSIZE) :: pustar ![m/s] wind friction speed
45 REAL, INTENT(IN), DIMENSION(KSIZE) :: prhoa ![kg/m3] air density at 2m height
46 REAL, INTENT(IN), DIMENSION(KSIZE) :: pclay ![frc] mass fraction clay
47 REAL, INTENT(IN), DIMENSION(KSIZE) :: psand ![frc] mass fraction sand
48 REAL, INTENT(IN), DIMENSION(KSIZE) :: pwg ![m3 m-3] volumetric water fraction
49 REAL, INTENT(IN), DIMENSION(KSIZE) :: pwsat ![m3 m-3] saturation water content
50 REAL, INTENT(IN), DIMENSION(KSIZE) :: pz0 ![m] surface roughness length
51 REAL, INTENT(IN), DIMENSION(KSIZE) :: pwind10m ![m/s] wind at 10m altitude
52 !OUTPUT the flux of dust
53 REAL, INTENT(OUT), DIMENSION(KSIZE) :: psfdst ! [kg m-2 s-1] Output flux of atmospheric dust
54 
55 !!!!!!!&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&!!!!!!
56 
57 !#ifdef AlG01
58 !REAL,PARAMETER::XFLX_MSS_FDG_FCT=28. ! [frc] Global mass flux tuning factor (a posteriori)
59 !#else
60 !REAL,PARAMETER::XFLX_MSS_FDG_FCT=7.0e-4 ! [frc] Global mass flux tuning factor (a posteriori)
61 !REAL,PARAMETER::XFLX_MSS_FDG_FCT=21.0e-4 ! [frc] Global mass flux tuning factor (a posteriori)
62  !real,PARAMETER::XFLX_MSS_FDG_FCT=12.0e-4 ! [frc] values used in Masdev47
63 !REAL,PARAMETER::flx_mss_fdg_fctm=4.0e-4 ! [frc] Global mass flux tuning factor (a posteriori) (proposez by Pierre)
64 !
65 !Define local variables:
66 LOGICAL, DIMENSION(KSIZE) :: gflg_mbl ! [frc] Mobilization candidate flag
67 REAL, DIMENSION(KSIZE) :: zmbl_bsn_fct ! [frc] enhancement factor for grid cells with higher erodibility
68 !REAL, DIMENSION(KSIZE) :: ZWND_RFR ! [m s-1] wind speed at reference level
69 REAL, DIMENSION(KSIZE) :: zwnd_frc_thr_slt ! [m/s] Threshold wind friction speed when all effects taken into account
70 REAL, DIMENSION(KSIZE) :: zgwc_sfc ! [kg/kg] Gravimetric water content
71 REAL, DIMENSION(KSIZE) :: zgwc_thr ! [kg kg-1] Threshold gravimetric water content
72 REAL, DIMENSION(KSIZE) :: zfrc_thr_ncr_wtr ! [frc] Fraction by which soil wetness increases threshold wind
73 REAL, DIMENSION(KSIZE) :: zfrc_thr_ncr_drg ! [frc] fraction by which drag partitioning increases threshold wind
74 REAL, DIMENSION(KSIZE) :: zwnd_frc_slt ! [m/s] wind friction speed after modified for saltation feedbacks
75 !REAL, DIMENSION(KSIZE) :: ZWND_RFR_THR_SLT ! [m s-1] Threshold wind speed at reference level
76 REAL, DIMENSION(KSIZE) :: zcoef
77 REAL, DIMENSION(KSIZE) :: zflx_mss_hrz_slt_ttl_wbn ! [kg m-1 s-1] Vertically integrated horizontal saltation soil flux for a wind bin
78 REAL, DIMENSION(KSIZE) :: zflx_mss_vrt_dst_ttl_wbn ! [kg m-2 s-1]
79 REAL, DIMENSION(KSIZE) :: zdst_slt_flx_rat_ttl ! [m-1] ratio of vertical to horizontal flux (alpha in several papers)
80 !
81 real :: zclay(ksize)
82 INTEGER :: i !Counter for number of points (used in loops)
83 REAL(KIND=JPRB) :: zhook_handle
84 
85 !Allocate the local variables
86 IF (lhook) CALL dr_hook('DUSTFLUX_GET',0,zhook_handle)
87 !
88 zclay(:)=0.2
89 !Initialize mobilization candidate flag
90 gflg_mbl(:) = .true.
91 !fxm: Get erodibility limitation factor, use something connected to amount of sand
92 !Discuss with Valery Masson
93 zmbl_bsn_fct(:) = psand(:)
94 ! utilisé dans le calcul de l'effet Owen
95 !ZWND_RFR(:) = PWIND10M(:)
96 !
97 !Initialize vertical dust flux
98 zflx_mss_vrt_dst_ttl_wbn(:) = 0.d0
99 !
100 ! Old Alf Grini code: bug on DEAD detected ?
101 ! Modification proposed by M. Mokhtari.. Accepted for all cases
102 ! if (CVERMOD=='CMDVER') then
103 zgwc_thr(:) = min(0.14,max(0.02,3. * pclay(:) * (0.17 + 0.14 * pclay(:))))
104 !ZGWC_THR(:) = PCLAY(:) * (0.17d0 + 0.14d0 * PCLAY(:))
105 ! else
106 ! gwc_thr=mss_frc_cly*(0.17d0+0.14d0*mss_frc_cly) ! [m3 m-3] FMB99 p. 155 (14)
107 ! fxm: 19991105 remove factor of mss_frc_cly from gwc_thr to improve large scale behavior
108 ! Begin Old Alf code
109 ! gwc_thr(lon_idx)=0.17d0+0.14d0*mss_frc_cly(lon_idx) ! [m3 m-3]
110 ! endif
111 !
112 ! Factor by which surface roughness increases threshold friction velocity
113 !++grini: fxm: USE WHOLE ARRAY OF Z0 INSTEAD OF ONLY RGH_MMN_MBL AS IN OLD CODE
114 DO i = 1,SIZE(pz0)
115  CALL frc_thr_ncr_drg_get(pz0(i), xrgh_mmn_smt, zfrc_thr_ncr_drg(i))
116 ENDDO
117 !
118 ! Convert volumetric water content to gravimetric water content
119  CALL vwc2gwc(gflg_mbl, pwsat, pwg, zgwc_sfc)
120 ! Factor by which soil moisture increases threshold friction velocity
121  CALL frc_thr_ncr_wtr_get(gflg_mbl, zgwc_thr, zgwc_sfc, zfrc_thr_ncr_wtr)
122 !
123 ! fxm: Use surface density not midlayer density
124  CALL wnd_frc_thr_slt_get(prhoa, xdmt_slt_opt, zwnd_frc_thr_slt)
125 !
126 DO i = 1, ksize
127  zwnd_frc_thr_slt(i) = & ! [m s-1] Threshold friction velocity for saltation
128  zwnd_frc_thr_slt(i) * & ! [m s-1] Threshold for dry, flat ground
129  zfrc_thr_ncr_wtr(i) ! [frc] Adjustment for moisture
130 ENDDO
131 !
132 ! Threshold saltation wind speed
133 !Needed for the saltation feedback roughening effect
134 !do i=1,KSIZE
135 ! if (flg_mbl(i)) then
136 ! wnd_rfr_thr_slt(i)= & ! [m s-1] Threshold 10 m wind speed for saltation
137 ! wnd_rfr(i)*wnd_frc_thr_slt(i)/PUSTAR(i) !++alfgr
138 ! endif ! endif flg_mbl
139 !end do ! end loop over lon
140 
141 !CHECK IF THIS CAN BE USED EASILY
142 !NEEDS 10M WIND SPEED WHICH IS MAYBE KNOWN MAYBE NOT !
143 ! Saltation increases friction speed by roughening surface
144 !call wnd_frc_slt_get( &
145 ! flg_mbl, & ! I [flg] Mobilization candidate flag
146 ! PUSTAR, & ! I [m s-1] Surface friction velocity
147 ! wnd_frc_slt, & ! O [m s-1] Saltating friction velocity
148 ! wnd_rfr, & ! I [m s-1] Wind speed at reference height
149 ! wnd_rfr_thr_slt) ! I [m s-1] Threshold 10 m wind speed for saltation
150 !
151 !
152 !Skip the roughening of surface effect for now, and
153 !just use the wind friction speed as it is modified
154 !by drag partitioning
155 zwnd_frc_slt(:) = pustar(:) / zfrc_thr_ncr_drg(:)
156 !
157 ! Horizontal streamwise mass flux for old "bulk" formulation
158 zcoef(:) = xcst_slt
159  CALL flx_mss_hrz_slt_ttl_whi79_get(zcoef, gflg_mbl, prhoa, zwnd_frc_slt, &
160  zwnd_frc_thr_slt, zflx_mss_hrz_slt_ttl_wbn)
161 !
162 ! Apply land surface and vegetation limitations and global tuning factor
163 DO i = 1, ksize
164  zflx_mss_hrz_slt_ttl_wbn(i) = zflx_mss_hrz_slt_ttl_wbn(i) & ! [kg m-2 s-1]
165  !*lnd_frc_mbl(i) & ! [frc] Bare ground fraction
166  * zmbl_bsn_fct(i) & ! [frc] Erodibility factor
167  * xflx_mss_fdg_fct ! [frc] Global mass flux tuning factor (empirical)
168 ENDDO
169 !
170 ! Vertical dust mass flux
171  CALL flx_mss_vrt_dst_ttl_mab95_get(gflg_mbl, zclay, zflx_mss_hrz_slt_ttl_wbn, &
172  zdst_slt_flx_rat_ttl, zflx_mss_vrt_dst_ttl_wbn)
173 !
174 !Assign the output vertical dust flux to the value calculated
175 !PSFDST(:) = flx_mss_vrt_dst_ttl_wbn(:)
176 psfdst(:) = zdst_slt_flx_rat_ttl(:) * zflx_mss_hrz_slt_ttl_wbn(:)
177 !
178 IF (lhook) CALL dr_hook('DUSTFLUX_GET',1,zhook_handle)
179 !
180 END SUBROUTINE dustflux_get
subroutine wnd_frc_thr_slt_get(PDNS_MDP, PDP, PWND_FRC_THR_SLT)
subroutine dustflux_get(PUSTAR, PRHOA, PWG, PZ0, PWSAT, PCLAY, PSAND, PWIND10M, PSFDST, KSIZE)
Definition: dustflux_get.F90:5
subroutine frc_thr_ncr_wtr_get(OFLG_MBL, PGWC_THR, PGWC_SFC, PFRC_THR_NCR_WTR)
subroutine vwc2gwc(OFLG_MBL, PVWC_SAT, PVWC_SFC, PGWC_SFC)
subroutine flx_mss_vrt_dst_ttl_mab95_get(OFLG_MBL, PMSS_FRC_CLY, PFLX_MSS_HRZ_SLT_TTL, PDST_SLT_FLX_RAT_TTL, PFLX_MSS_VRT_DST_TTL)
subroutine frc_thr_ncr_drg_get(PRGH_MMN_MBL, PRGH_MMN_SMT, PFRC_THR_NCR_DRG)
subroutine flx_mss_hrz_slt_ttl_whi79_get(PCOEFF, OFLG_MBL, PDNS_MDP, PWND_FRC, PWND_FRC_THR_SLT, PFLX_MSS_HRZ_SLT_TTL)