source: trunk/LMDZ.GENERIC/libf/phystd/thermcell_alim.F90 @ 2066

Last change on this file since 2066 was 2066, checked in by aboissinot, 6 years ago

Fix f0 saving
Restore d_temp functionality. d_temp is set in thermcell_mod and used in thermcell_alim.
d_temp is a virtual potential temperature offset applied only in layer linf.
Remove a potential division by zero in thermcell_plume with variable zw2m.

File size: 2.9 KB
Line 
1!
2!
3!
4      SUBROUTINE thermcell_alim(flag,ngrid,klev,ztv,zlev,alim_star,           &
5                                lalim,lmin)
6     
7     
8      USE thermcell_mod, ONLY: linf, d_temp
9     
10      IMPLICIT NONE
11     
12!==============================================================================
13! FH : 2015/11/06
14! thermcell_alim: calcule la distribution verticale de l'alimentation
15! laterale a la base des panaches thermiques
16!==============================================================================
17     
18     
19!==============================================================================
20! Declaration
21!==============================================================================
22     
23!      inputs:
24!      -------
25     
26      INTEGER, INTENT(IN) :: ngrid
27      INTEGER, INTENT(IN) :: klev
28      INTEGER, INTENT(IN) :: lmin(ngrid)        ! plume initial level
29      INTEGER, INTENT(IN) :: flag               ! useless here
30     
31      REAL, INTENT(IN) :: ztv(ngrid,klev)       ! Large scale virtual potential temperature
32! Virtual potential temperature offset in linf layer
33      REAL, INTENT(IN) :: zlev(ngrid,klev+1)    ! levels altitude
34     
35!      outputs:
36!      --------
37     
38      INTEGER, INTENT(OUT) :: lalim(ngrid)      ! alimentation maximal level
39     
40      REAL, INTENT(OUT) :: alim_star(ngrid,klev)
41     
42!      local:
43!      ------
44     
45      INTEGER :: ig, l
46     
47      REAL :: alim_star_tot(ngrid)              ! integrated alimentation
48      REAL :: ztv2(ngrid,klev)                  ! ztv + d_temp
49     
50!==============================================================================
51! Initialization
52!==============================================================================
53     
54      lalim(:) = 1
55     
56      alim_star_tot(:) = 0.
57     
58      ztv2(:,:) = ztv(:,:)
59      ztv2(:,linf) = ztv2(:,linf) + d_temp
60     
61!==============================================================================
62! Alimentation computation
63!==============================================================================
64     
65      DO l=lmin(ig),klev-1
66         DO ig=1,ngrid
67            IF ((ztv2(ig,l)>ztv2(ig,l+1)).and.(ztv2(ig,lmin(ig))>=ztv2(ig,l))) THEN
68               alim_star(ig,l) = MAX( (ztv2(ig,l) - ztv2(ig,l+1)), 0.)  &
69               &               * sqrt(zlev(ig,l+1))
70               lalim(ig) = l + 1
71               alim_star_tot(ig) = alim_star_tot(ig) + alim_star(ig,l)
72            ELSE
73               alim_star(ig,l) = 0.
74            ENDIF
75         ENDDO
76      ENDDO
77     
78!------------------------------------------------------------------------------
79! Alimentation normalization
80!------------------------------------------------------------------------------
81     
82      DO l=1,klev
83         DO ig=1,ngrid
84            IF (alim_star_tot(ig) > 1.e-10 ) THEN
85               alim_star(ig,l) = alim_star(ig,l) / alim_star_tot(ig)
86            ENDIF
87         ENDDO
88      ENDDO
89     
90      alim_star_tot(:) = 1.
91     
92     
93RETURN
94END
Note: See TracBrowser for help on using the repository browser.