source: trunk/LMDZ.GENERIC/libf/phystd/thermcell_closure.F90 @ 2145

Last change on this file since 2145 was 2145, checked in by aboissinot, 5 years ago

Some temporary outputs in thermcell_closure are removed and a bug in
thermcell_plume is fixed.

File size: 3.4 KB
Line 
1!
2!
3!
4SUBROUTINE thermcell_closure(ngrid,nlay,ptimestep,rho,zlev,                   &
5                             lmax,alim_star,zmin,zmax,wmax,f)
6     
7     
8!===============================================================================
9!  Purpose: fermeture, determination de f
10!
11! Modification 7 septembre 2009
12! 1. On enleve alim_star_tot des arguments pour le recalculer et etre ainis
13! coherent avec l'integrale au numerateur.
14! 2. On ne garde qu'une version des couples wmax,zmax et wmax_sec,zmax_sec
15! l'idee etant que le choix se fasse a l'appel de thermcell_closure
16! 3. Vectorisation en mettant les boucles en l a l'exterieur avec des if
17!===============================================================================
18     
19      USE thermcell_mod
20     
21      IMPLICIT NONE
22     
23     
24!===============================================================================
25! Declaration
26!===============================================================================
27     
28!     Inputs:
29!     -------
30     
31      INTEGER ngrid, nlay
32      INTEGER lmax(ngrid)
33     
34      REAL ptimestep
35      REAL rho(ngrid,nlay)
36      REAL zlev(ngrid,nlay)
37      REAL alim_star(ngrid,nlay)
38      REAL zmin(ngrid)
39      REAL zmax(ngrid)
40      REAL wmax(ngrid)
41     
42!     Outputs:
43!     --------
44     
45      REAL f(ngrid)
46     
47!     Local:
48!     ------
49     
50      INTEGER ig, l
51      INTEGER llmax
52     
53      REAL alim_star_tot(ngrid)
54      REAL alim_star2(ngrid)
55      REAL plume_height(ngrid)
56     
57!===============================================================================
58! Initialization
59!===============================================================================
60     
61      alim_star2(:) = 0.
62      alim_star_tot(:) = 0.
63     
64      f(:) = 0.
65     
66      llmax = 1
67     
68      DO ig=1,ngrid
69         plume_height(ig) = zmax(ig) - zmin(ig)
70      ENDDO
71     
72!===============================================================================
73! Closure
74!===============================================================================
75     
76!-------------------------------------------------------------------------------
77! Indice vertical max atteint par les thermiques sur le domaine
78!-------------------------------------------------------------------------------
79     
80      DO ig=1,ngrid
81         IF (lmax(ig) > llmax) THEN
82            llmax = lmax(ig)
83         ENDIF
84      ENDDO
85     
86!-------------------------------------------------------------------------------
87! Calcul des integrales sur la verticale de alim_star et de alim_star^2/(rho dz)
88!-------------------------------------------------------------------------------
89     
90      DO l=1,llmax-1
91         DO ig=1,ngrid
92            IF (l < lmax(ig)) THEN
93               alim_star2(ig) = alim_star2(ig) + alim_star(ig,l)**2           &
94               &              / (rho(ig,l) * (zlev(ig,l+1) - zlev(ig,l)))        ! => intergration is ok because alim_star = a* dz
95               alim_star_tot(ig) = alim_star_tot(ig) + alim_star(ig,l)
96            ENDIF
97         ENDDO
98      ENDDO
99     
100      DO ig=1,ngrid
101         IF ((alim_star2(ig) > 0.).and.(plume_height(ig) > 0.)) THEN
102            f(ig) = wmax(ig) * alim_star_tot(ig)                              &  ! => normalization is ok
103            &     / (plume_height(ig) * r_aspect_thermals * alim_star2(ig))
104         ELSE
105            f(ig) = 0.
106         ENDIF
107      ENDDO
108     
109     
110RETURN
111END
Note: See TracBrowser for help on using the repository browser.