source: LMDZ6/trunk/libf/phylmd/Dust/bcscav_spl.f90 @ 5354

Last change on this file since 5354 was 5337, checked in by Laurent Fairhead, 3 weeks ago

Getting rid of dependance to dynamics

File size: 1.6 KB
Line 
1SUBROUTINE bcscav_spl(pdtime,flxr,flxs,alpha_r,alpha_s,x,dx)
2
3  USE dimphy
4  USE yomcst_mod_h
5  USE yoecumf_mod_h
6  USE chem_mod_h
7IMPLICIT NONE
8  !=====================================================================
9  ! Objet : below-cloud scavenging of tracers
10  ! Date : september 1999
11  ! Auteur: O. Boucher (LOA)
12  !=====================================================================
13
14  !
15  REAL :: pdtime, alpha_r, alpha_s, R_r, R_s
16  PARAMETER (R_r=0.001)          !--mean raindrop radius (m)
17  PARAMETER (R_s=0.001)          !--mean snow crystal radius (m)
18  REAL :: flxr(klon,klev)         ! liquid precipitation rate (kg/m2/s)
19  REAL :: flxs(klon,klev)         ! solid  precipitation rate (kg/m2/s)
20  REAL :: flxr_aux(klon,klev+1)
21  REAL :: flxs_aux(klon,klev+1)
22  REAL :: x(klon,klev)              ! q de traceur
23  REAL :: dx(klon,klev)             ! tendance de traceur
24  !
25  !--variables locales
26  INTEGER :: i, k
27  REAL :: pr, ps, ice, water
28  !
29  !------------------------------------------
30  !
31  ! NHL
32  ! Auxiliary variables defined to deal with the fact that precipitation
33  ! fluxes are defined on klev levels only.
34  ! NHL
35  !
36  flxr_aux(:,klev+1)=0.0
37  flxs_aux(:,klev+1)=0.0
38  flxr_aux(:,1:klev)=flxr(:,:)
39  flxs_aux(:,1:klev)=flxs(:,:)
40  !
41  DO k=1, klev
42  DO i=1, klon
43   pr=0.5*(flxr_aux(i,k)+flxr_aux(i,k+1))
44   ps=0.5*(flxs_aux(i,k)+flxs_aux(i,k+1))
45   water=pr*alpha_r/R_r/rho_water
46   ice=ps*alpha_s/R_s/rho_ice
47   dx(i,k)=-3./4.*x(i,k)*pdtime*(water+ice)
48  !tmp       dx(i,k)=-3./4.*x(i,k)*pdtime*
49  !tmp     .         (pr*alpha_r/R_r/rho_water+ps*alpha_s/R_s/rho_ice)
50  ENDDO
51  ENDDO
52  !
53  RETURN
54END SUBROUTINE bcscav_spl
Note: See TracBrowser for help on using the repository browser.