Ignore:
Timestamp:
Jan 14, 2010, 3:35:30 PM (14 years ago)
Author:
Laurent Fairhead
Message:

Modifications pour la nouvelle version des thermiques (2009/2010) CR et FH

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/phylmd/thermcell_dry.F90

    r938 r1294  
     1!
     2! $Header$
     3!
    14       SUBROUTINE thermcell_dry(ngrid,nlay,zlev,pphi,ztv,alim_star,  &
    25     &                            lalim,lmin,zmax,wmax,lev_out)
     
    47!--------------------------------------------------------------------------
    58!thermcell_dry: calcul de zmax et wmax du thermique sec
     9! Calcul de la vitesse maximum et de la hauteur maximum pour un panache
     10! ascendant avec une fonction d'alimentation alim_star et sans changement
     11! de phase.
     12! Le calcul pourrait etre sans doute simplifier.
     13! La temperature potentielle virtuelle dans la panache ascendant est
     14! la temperature potentielle virtuelle pondérée par alim_star.
    615!--------------------------------------------------------------------------
     16
    717       IMPLICIT NONE
    818#include "YOMCST.h"       
     
    4858!calcul de la vitesse a partir de la CAPE en melangeant thetav
    4959
    50 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    51 ! A eliminer
    52 ! Ce if complique etait fait pour reperer la premiere couche instable
    53 ! Ici, c'est lmin.
    54 !
    55 !       do l=1,nlay-2
    56 !         do ig=1,ngrid
    57 !            if (ztv(ig,l).gt.ztv(ig,l+1)  &
    58 !     &         .and.alim_star(ig,l).gt.1.e-10  &
    59 !     &         .and.zw2(ig,l).lt.1e-10) then
    60 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    61 
    6260
    6361! Calcul des F^*, integrale verticale de E^*
     
    8482!  Premiere couche du panache thermique
    8583!------------------------------------------------------------------------
     84
    8685               zw2(ig,l+1)=2.*RG*(ztv(ig,l)-ztv(ig,l+1))/ztv(ig,l+1)  &
    8786     &                     *(zlev(ig,l+1)-zlev(ig,l))  &
     
    9695! 3. la vitesse au carré en haut zw2(ig,l+1)
    9796!------------------------------------------------------------------------
    98 
    99 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    100 !  A eliminer : dans cette version, si zw2 est > 0 on a un therique.
    101 !  et donc, au dessus, f_star(ig,l+1) est forcement suffisamment
    102 !  grand puisque on n'a pas de detrainement.
    103 !  f_star est une fonction croissante.
    104 !  c'est donc vraiment sur zw2 uniquement qu'il faut faire le test.
    105 !           else if ((zw2(ig,l).ge.1e-10).and.  &
    106 !    &               (f_star(ig,l)+alim_star(ig,l).gt.1.e-10)) then
    107 !              f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)
    108 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    10997
    11098            else if (zw2(ig,l).ge.1e-10) then
     
    145133       if (prt_level.ge.1) print*,'fin calcul zw2'
    146134!
    147 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    148 ! A eliminer :
    149 ! Ce calcul de lmax est fait en meme temps que celui de linter, plus haut
    150 ! Calcul de la couche correspondant a la hauteur du thermique
    151 !      do ig=1,ngrid
    152 !         lmax(ig)=lalim(ig)
    153 !      enddo
    154 !      do ig=1,ngrid
    155 !         do l=nlay,lalim(ig)+1,-1
    156 !            if (zw2(ig,l).le.1.e-10) then
    157 !               lmax(ig)=l-1
    158 !            endif
    159 !         enddo
    160 !      enddo
    161 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    162 
    163 !   
    164135! Determination de zw2 max
    165136      do ig=1,ngrid
     
    185156      do  ig=1,ngrid
    186157! calcul de zlevinter
    187 
    188 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    189 ! FH A eliminer
    190 ! Simplification
    191 !          zlevinter(ig)=(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))*  &
    192 !     &    linter(ig)+zlev(ig,lmax(ig))-lmax(ig)*(zlev(ig,lmax(ig)+1)  &
    193 !     &    -zlev(ig,lmax(ig)))
    194 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    195 
    196158          zlevinter(ig)=zlev(ig,lmax(ig)) + &
    197159     &    (linter(ig)-lmax(ig))*(zlev(ig,lmax(ig)+1)-zlev(ig,lmax(ig)))
     
    199161      enddo
    200162
    201 ! Verification que lalim<=lmax
    202       do ig=1,ngrid
    203          if(lalim(ig)>lmax(ig)) then
    204            if ( prt_level > 1 ) THEN
    205             print*,'WARNING thermcell_dry ig=',ig,'  lalim=',lalim(ig),'  lmax(ig)=',lmax(ig)
    206            endif
    207            lmax(ig)=lalim(ig)
    208          endif
    209       enddo
    210      
    211163      RETURN
    212164      END
Note: See TracChangeset for help on using the changeset viewer.