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

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

Fix a bug in thermcell_alim.F90 where vertical and horizontal loops must be inverted.
In thermal plume model, arrays size declaration is standardised (no longer done thanks to dimphy module but by way of arguments).
Clean up some thermal plume model routines (remove uselesss variables...)

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