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

Last change on this file since 2099 was 2093, checked in by aboissinot, 7 years ago

d_temp is now taken into acocunt in thermcell_plume to trigger the plume and compute first unstable layer speed.
Modified temperature is computed in thermcell_plume and thermcell_alim get it via its arguments.

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