source: LMDZ6/trunk/libf/phylmd/Dust/incloud_scav.f90 @ 5277

Last change on this file since 5277 was 5274, checked in by abarral, 9 hours ago

Replace yomcst.h by existing module

File size: 4.1 KB
Line 
1! Subroutine that calculates the effect of precipitation in scavenging
2! WITHIN the cloud, for large scale as well as convective precipitation
3SUBROUTINE incloud_scav(lminmax,qmin,qmax,masse,henry,kk,prfl, &
4        psfl,pmflxr,pmflxs,zrho,zdz,t_seri,pdtphys, &
5        his_dhlsc,his_dhcon1,tr_seri)
6
7  USE dimphy
8  USE infotrac
9  USE indice_sol_mod
10
11  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
12USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
13          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
14USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
15          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
16          , R_ecc, R_peri, R_incl                                      &
17          , RA, RG, R1SA                                         &
18          , RSIGMA                                                     &
19          , R, RMD, RMV, RD, RV, RCPD                    &
20          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
21          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
22          , RCW, RCS                                                 &
23          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
24          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
25          , RALPD, RBETD, RGAMD
26IMPLICIT NONE
27
28
29  INCLUDE "chem.h"
30
31
32
33  !============================= INPUT ===================================
34  REAL :: qmin, qmax
35  REAL :: masse(nbtr)
36  REAL :: henry(nbtr)         !--cste de Henry  mol/l/atm
37  REAL :: kk(nbtr)            !--coefficient de var avec T (K)
38  REAL :: prfl(klon,klev+1),   psfl(klon,klev+1)     !--large-scale
39   ! REAL prfl(klon,klev),   psfl(klon,klev)     !--large-scale
40  REAL :: pmflxr(klon,klev+1), pmflxs(klon,klev+1)   !--convection
41   ! REAL pmflxr(klon,klev), pmflxs(klon,klev)   !--convection
42  REAL :: zrho(klon,klev), zdz(klon,klev)
43  REAL :: t_seri(klon,klev)
44  LOGICAL :: lminmax
45  REAL :: pdtphys
46   ! REAL prfl(klon,klev+1),   psfl(klon,klev+1)     !--large-scale  ! Titane
47   ! REAL pmflxr(klon,klev+1), pmflxs(klon,klev+1)   !--convection   ! Titane
48  !============================= OUTPUT ==================================
49  REAL :: tr_seri(klon,klev,nbtr) ! traceur
50  REAL :: aux_var1(klon,klev) ! traceur
51  REAL :: aux_var2(klon) ! traceur
52  REAL :: aux_var3(klon) ! traceur
53  REAL :: his_dhlsc(klon,nbtr)        ! in-cloud scavenging lsc
54  REAL :: his_dhcon1(klon,nbtr)       ! in-cloud scavenging con
55  !========================= LOCAL VARIABLES =============================
56  INTEGER :: it, i, j
57
58  EXTERNAL minmaxqfi, inscav_spl
59
60  DO it=1, nbtr
61  !
62  DO i=1,klon
63    aux_var2(i)=his_dhlsc(i,it)
64    aux_var3(i)=his_dhcon1(i,it)
65  ENDDO
66  DO j=1,klev
67  DO i=1,klon
68    aux_var1(i,j)=tr_seri(i,j,it)
69  ENDDO
70  ENDDO
71  !
72  IF (lminmax) THEN
73    CALL minmaxqfi(aux_var1,qmin,qmax,'avt inscav')
74  !nhl      CALL minmaxqfi(tr_seri(1,1,it),qmin,qmax,'avt inscav')
75  ENDIF
76  !
77  !nhl      CALL inscav_spl(pdtphys,it,masse(it),henry(it),kk(it),0.5e-3,
78  !nhl     .             prfl,psfl,zrho,zdz,t_seri,tr_seri(1,1,it),
79  !nhl     .             his_dhlsc(1,it))
80  CALL inscav_spl(pdtphys,it,masse(it),henry(it),kk(it),0.5e-3, &
81        prfl,psfl,zrho,zdz,t_seri,aux_var1,aux_var2)
82  !
83  IF (lminmax) THEN
84    CALL minmaxqfi(aux_var1,qmin,qmax,'depot humide lsc')
85  !nhl      CALL minmaxqfi(tr_seri(1,1,it),qmin,qmax,'depot humide lsc')
86  ENDIF
87  !
88  !
89  !-scheme for convective in-cloud scavenging
90  !
91  !nhl      CALL inscav_spl(pdtphys,it,masse(it),henry(it),kk(it),1.e-3,
92  !nhl     .             pmflxr,pmflxs,zrho,zdz,t_seri,tr_seri(1,1,it),
93  !nhl     .             his_dhcon1(1,it))
94  CALL inscav_spl(pdtphys,it,masse(it),henry(it),kk(it),1.e-3, &
95        pmflxr,pmflxs,zrho,zdz,t_seri,aux_var1,aux_var3)
96  !
97  IF (lminmax) THEN
98    CALL minmaxqfi(aux_var1,qmin,qmax,'depot humide con')
99  !nhl      CALL minmaxqfi(tr_seri(1,1,it),qmin,qmax,'depot humide con')
100  ENDIF
101  !
102  DO j=1,klev
103  DO i=1,klon
104    tr_seri(i,j,it)=aux_var1(i,j)
105  ENDDO
106  ENDDO
107  DO i=1,klon
108    his_dhlsc(i,it)=aux_var2(i)
109    his_dhcon1(i,it)=aux_var3(i)
110  ENDDO
111
112  !
113  ENDDO !--boucle sur it
114
115END SUBROUTINE incloud_scav
Note: See TracBrowser for help on using the repository browser.