source: LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_thermcell_height.F90

Last change on this file was 5158, checked in by abarral, 3 months ago

Add missing klon on strataer_emiss_mod.F90
Correct various missing explicit declarations
Replace tabs by spaces (tabs are not part of the fortran charset)
Continue cleaning modules
Removed unused arguments and variables

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.1 KB
RevLine 
[4590]1MODULE lmdz_thermcell_height
2CONTAINS
3
[4843]4      SUBROUTINE thermcell_height(ngrid,nlay,lalim,lmin,linter,lcong,lintercong,lmix,  &
[5087]5             zw2,zlev,lmax,zmax,zmax0,zmix,wmax,zcong)
[4094]6      IMPLICIT NONE
[878]7
8!-----------------------------------------------------------------------------
9!thermcell_height: calcul des caracteristiques du thermique: zmax,wmax,zmix
10!-----------------------------------------------------------------------------
11
[4094]12! arguments
[878]13
[4094]14! Entree
[5117]15      INTEGER, INTENT(IN) :: ngrid,nlay
16      REAL, INTENT(IN), DIMENSION(ngrid) :: linter,lintercong
17      REAL, INTENT(IN), DIMENSION(ngrid,nlay+1) :: zlev
[4094]18! Sortie
[5117]19      REAL, INTENT(OUT), DIMENSION(ngrid) :: wmax,zmax,zmax0,zmix,zcong
20      INTEGER, INTENT(OUT), DIMENSION(ngrid) :: lmax,lcong
[4094]21! Les deux
[5117]22     INTEGER, INTENT(INOUT), DIMENSION(ngrid) :: lmix,lalim,lmin
23     REAL, INTENT(INOUT), DIMENSION(ngrid,nlay+1) :: zw2
[878]24
[4094]25! local
[5117]26     REAL, DIMENSION(ngrid) :: num,denom,zlevinter,zlevintercong
27     INTEGER ig,l
[878]28
29!calcul de la hauteur max du thermique
[5158]30      DO ig=1,ngrid
[878]31         lmax(ig)=lalim(ig)
32      enddo
[5158]33      DO ig=1,ngrid
34         DO l=nlay,lalim(ig)+1,-1
[5117]35            IF (zw2(ig,l)<=1.e-10) THEN
[878]36               lmax(ig)=l-1
37            endif
38         enddo
39      enddo
[1403]40
[5093]41! On traite le cas particulier qu'il faudrait éviter ou le thermique
[1403]42! atteind le haut du modele ...
[5158]43      DO ig=1,ngrid
[5117]44      IF ( zw2(ig,nlay) > 1.e-10 ) THEN
[5103]45          PRINT*,'WARNING !!!!! W2 thermiques non nul derniere couche '
[1403]46          lmax(ig)=nlay
47      endif
48      enddo
49
[878]50! pas de thermique si couche 1 stable
[5158]51      DO ig=1,ngrid
[5117]52         IF (lmin(ig)>1) THEN
[878]53             lmax(ig)=1
54             lmin(ig)=1
55             lalim(ig)=1
56         endif
57      enddo
[5099]58
[878]59! Determination de zw2 max
[5158]60      DO ig=1,ngrid
[878]61         wmax(ig)=0.
62      enddo
63
[5158]64      DO l=1,nlay
65         DO ig=1,ngrid
[5117]66            IF (l<=lmax(ig)) THEN
67                IF (zw2(ig,l)<0.)THEN
[5103]68                  PRINT*,'pb2 zw2<0'
[878]69                endif
70                zw2(ig,l)=sqrt(zw2(ig,l))
71                wmax(ig)=max(wmax(ig),zw2(ig,l))
72            else
73                 zw2(ig,l)=0.
74            endif
75          enddo
76      enddo
77
78!   Longueur caracteristique correspondant a la hauteur des thermiques.
[5158]79      DO  ig=1,ngrid
[878]80         zmax(ig)=0.
81         zlevinter(ig)=zlev(ig,1)
82      enddo
[1026]83
[5116]84!     if (iflag_thermals_ed.ge.1) THEN
[5117]85      IF (1==0) THEN
[1998]86!CR:date de quand le calcul du zmax continu etait buggue
[1026]87         num(:)=0.
88         denom(:)=0.
[5158]89         DO ig=1,ngrid
90          DO l=1,nlay
[1026]91             num(ig)=num(ig)+zw2(ig,l)*zlev(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
92             denom(ig)=denom(ig)+zw2(ig,l)*(zlev(ig,l+1)-zlev(ig,l))
93          enddo
94       enddo
[5158]95       DO ig=1,ngrid
[5117]96       IF (denom(ig)>1.e-10) THEN
[1026]97          zmax(ig)=2.*num(ig)/denom(ig)
98          zmax0(ig)=zmax(ig)
99       endif
100       enddo
[1998]101 
102      else
103!CR:Calcul de zmax continu via le linter     
[5158]104      DO  ig=1,ngrid
[878]105! calcul de zlevinter
106          zlevinter(ig)=(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))*  &
[5087]107      linter(ig)+zlev(ig,lmax(ig))-lmax(ig)*(zlev(ig,lmax(ig)+1)  &
108      -zlev(ig,lmax(ig)))
[878]109!pour le cas ou on prend tjs lmin=1
110!       zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,lmin(ig)))
111       zmax(ig)=max(zmax(ig),zlevinter(ig)-zlev(ig,1))
112       zmax0(ig)=zmax(ig)
113      enddo
[1026]114
[4843]115!CR:calcul du zcong
[5158]116      DO  ig=1,ngrid
[4843]117! calcul de zlevintercong
118         zlevintercong(ig)=(zlev(ig,lcong(ig)+1)-zlev(ig,lcong(ig)))*  &
[5087]119      lintercong(ig)+zlev(ig,lcong(ig))-lcong(ig)*(zlev(ig,lcong(ig)+1)  &
120      -zlev(ig,lcong(ig)))
[4843]121         zcong(ig)=zlevintercong(ig)-zlev(ig,1)
[5103]122!         PRINT*,"calcul zcong",lcong(ig),lintercong(ig),zlevintercong(ig),zcong(ig)
[4843]123      enddo
[1026]124
125      endif
126!endif iflag_thermals_ed
[5099]127
[878]128! def de  zmix continu (profil parabolique des vitesses)
[5158]129      DO ig=1,ngrid
[5117]130           IF (lmix(ig)>1) THEN
[878]131! test
[5117]132              IF (((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))  &
[5087]133          *((zlev(ig,lmix(ig)))-(zlev(ig,lmix(ig)+1)))  &
134          -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))  &
135          *((zlev(ig,lmix(ig)-1))-(zlev(ig,lmix(ig)))))>1e-10)  &
[5116]136          THEN
[878]137            zmix(ig)=((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))  &
[5087]138          *((zlev(ig,lmix(ig)))**2-(zlev(ig,lmix(ig)+1))**2)  &
139          -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))  &
140          *((zlev(ig,lmix(ig)-1))**2-(zlev(ig,lmix(ig)))**2))  &
141          /(2.*((zw2(ig,lmix(ig)-1)-zw2(ig,lmix(ig)))  &
142          *((zlev(ig,lmix(ig)))-(zlev(ig,lmix(ig)+1)))  &
143          -(zw2(ig,lmix(ig))-zw2(ig,lmix(ig)+1))  &
144          *((zlev(ig,lmix(ig)-1))-(zlev(ig,lmix(ig))))))
[878]145              else
146              zmix(ig)=zlev(ig,lmix(ig))
[5103]147              PRINT*,'pb zmix'
[878]148              endif
149          else
150              zmix(ig)=0.
151          endif
152!test
[5117]153         IF ((zmax(ig)-zmix(ig))<=0.) THEN
[878]154            zmix(ig)=0.9*zmax(ig)
[5103]155!            PRINT*,'pb zmix>zmax'
[878]156         endif
157      enddo
[5099]158
[878]159! calcul du nouveau lmix correspondant
[5158]160      DO ig=1,ngrid
161         DO l=1,nlay
[5117]162            IF (zmix(ig)>=zlev(ig,l).AND.  &
[5116]163            zmix(ig)<zlev(ig,l+1)) THEN
[878]164              lmix(ig)=l
165             endif
166          enddo
167      enddo
[5099]168
[4094]169 RETURN
[5119]170      END
[4590]171END MODULE lmdz_thermcell_height
Note: See TracBrowser for help on using the repository browser.