source: LMDZ6/trunk/libf/phylmd/alpale_wk.f90

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

Replace yomcst.h by existing module

File size: 3.4 KB
Line 
1SUBROUTINE alpale_wk ( dtime, cell_area, zoccur, sigmaw, wdens, fip ,  &
2                       fip_cond)
3
4! **************************************************************
5!                                                              *
6! ALPALE_WK                                                    *
7!                                                              *
8!                                                              *
9! written by   : Jean-Yves Grandpeix, 07/08/2017               *
10! modified by :                                                *
11! **************************************************************
12
13  USE dimphy, ONLY: klon
14  USE ioipsl_getin_p_mod, ONLY : getin_p
15  USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
16  USE yomcst_mod_h, ONLY: rpi
17
18  IMPLICIT NONE
19
20!================================================================
21! Auteur(s)   : Jean-Yves Grandpeix, 07/08/2017
22! Objet : Contribution of the wake scheme to Ale and Alp
23!================================================================
24
25! Input arguments
26!----------------
27  REAL, INTENT(IN)                                           :: dtime
28  REAL, DIMENSION(klon),    INTENT(IN)                       :: cell_area
29  INTEGER, DIMENSION(klon), INTENT (IN)                      :: zoccur
30  REAL, DIMENSION(klon),    INTENT(IN)                       :: sigmaw
31  REAL, DIMENSION(klon),    INTENT(IN)                       :: wdens
32  REAL, DIMENSION(klon),    INTENT(IN)                       :: fip
33! Output arguments
34!-----------------
35  REAL, DIMENSION(klon), INTENT(OUT)                         :: fip_cond
36
37
38! Local variables
39!----------------
40  INTEGER                                                    :: i
41  LOGICAL, SAVE                                              :: first = .TRUE.
42  !$OMP THREADPRIVATE(first)
43  REAL, ALLOCATABLE, SAVE, DIMENSION(:)                      :: cellrad
44  !$OMP THREADPRIVATE(cellrad)
45  REAL, DIMENSION(klon)                                      :: wkrad
46  REAL, DIMENSION(klon)                                      :: proba_gf
47
48IF (first) THEN
49  ALLOCATE (cellrad(klon))
50!  Compute pseudo grid-cell radius cellrad, such that pi*cellrad^2=cell_area
51  print *,'alpale_wk: cell_area(1) ',cell_area(1)
52  cellrad(:)=sqrt(cell_area(:)/rpi)
53  first = .FALSE.
54ENDIF
55
56!  Compute wake radius
57!!  print *,'alpale_wk: sigmaw(1), wdens(1) ', sigmaw(1), wdens(1)
58  DO i = 1,klon
59    IF (zoccur(i) .GE. 1) THEN
60      wkrad(i) = sqrt(sigmaw(i)/(rpi*wdens(i)))
61    ELSE
62      wkrad(i) = 0.
63    ENDIF ! (zoccur(i) .GE. 1)
64  ENDDO
65
66!  Compute probability that the grid-cell is intersected by a gust front
67!!  print *,'alpale_wk: wkrad(1), cellrad(1) ', wkrad(1), cellrad(1)
68!!  proba_gf(:) = exp(-wdens(:)*rpi*max(wkrad(:)-cellrad(:),0.)**2) - &   ! Formules
69!!                exp(-wdens(:)*rpi*(wkrad(:)+cellrad(:))**2)             ! fausses !
70  proba_gf(:) = 1. - exp(-wdens(:)*rpi*((wkrad(:)+cellrad(:))**2 - &
71                                        max(wkrad(:)-cellrad(:),0.)**2) )
72!
73  proba_gf(:) = max(proba_gf(:),1.e-3)
74!  Compute Fip conditionned on the presence of some gust front within the
75!  grid-cell
76!!  print *,'alpale_wk: proba_gf(1), fip(1), ', proba_gf(1), fip(1)
77  fip_cond(:) = fip(:)/proba_gf(:)
78!!    print *,'alpale_wk: wkrad(1), cellrad(1), proba_gf(1), fip(1), fip_cond(1) ', &
79!!                        wkrad(1), cellrad(1), proba_gf(1), fip(1), fip_cond(1)
80
81   RETURN
82   END SUBROUTINE alpale_wk
83
Note: See TracBrowser for help on using the repository browser.