source: LMDZ5/trunk/libf/phylmd/alpale_wk.F90 @ 3001

Last change on this file since 3001 was 3001, checked in by jyg, 7 years ago

addendum to the previous commit

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